[BioC] heatmap

Adaikalavan Ramasamy gisar@nus.edu.sg
Sat, 22 Feb 2003 12:12:57 +0800


Thanks to Mark Wilkinson for pointing out my previous e-mail regarding
the Eisen Cluster & Treeview like plots.

It is in my humble opinion that a biologists/microarray like to see
pictures on a green and red scale indicating under/over expression. The
function plot.mat() by Sandrine Dudoit does the green-red coloring. You
can further include an option to z-score the rows before plotting. 

You can easily break my function (which I think you can find in the
archives, otherwise email me) so that the clusterings can be done
separately.

As with you, the other problem I had was that the row labels being
'squashed' too close. Another nice feature to include would be to have
interactive names. i.e. when you click on the plot, the name of the
corresponding gene pops up (like Treeview).

Regards, Adai.



-----Original Message-----
From: Liaw, Andy [mailto:andy_liaw@merck.com] 
Sent: Saturday, February 22, 2003 7:44 AM
To: 'rossini@u.washington.edu'
Cc: 'bioconductor@stat.math.ethz.ch'
Subject: RE: [BioC] heatmap


I probably should have given more detail on my attempt.  The help file
looks like the following:

==================
Heatmap of a data matrix

Description:

     Given a data matrix and clustering of its rows and columns, draw a
     heatmap along with dendrograms in the margins.

Usage:

     heatmap(x, r.hc, c.hc, add.expr, ...)

Arguments:

       x: The data matrix.

    r.hc: An `hclust' object representing clustering of rows.

    c.hc: An `hclust' object representing clustering of columns.

add.expr: An expression used to add graphics to the color image.

     ...: Arguments to be passed to `image', which draws the heatmap.

Details:

     `layout' is used to partition the plots.

     If `x' has row and column names, they will be used to label the
     heatmap.  Otherwise the row and column indices are used.

Value:

     `NULL'

Author(s):

     Andy Liaw

See Also:

     `image', `hclust'

Examples:

     set.seed(132)
     x <- matrix(runif(1000), 50, 20)
     row.hc <- hclust(dist(x))
     col.hc <- hclust(dist(t(x)))
     heatmap(x, row.hc, col.hc, add.expr=abline(h=20.5, col="blue",
lwd=2)) ===============================

(The output of the example code is attached.)

So, the clustering is done *before* the function is called.  It
basically rely on the plot(as.dendrogram(hclust.object)) to draw the
dendrograms (thus requires the "mva" package be loaded).  Also, I have
not figured out a good way to scale the size of the row and column
labels.  If anyone can suggest a good way to do that, I'll be very
grateful.

The function is rather simple, so I'll show it below.  Any
comments/fixes/improvements etc. welcomed.

Cheers,
Andy ==============================================================
heatmap <- function (x, r.hc, c.hc, add.expr, ...) 
{
    op <- par(no.readonly = TRUE)
    on.exit(par(op))
    r.cex <- 0.2 + 1/log10(nrow(x))
    c.cex <- 0.2 + 1/log10(ncol(x))
    x <- x[r.hc$order, c.hc$order]
    layout(matrix(c(0, 3, 2, 1), 2, 2, byrow = TRUE), widths = c(1, 
        4), heights = c(1, 4), respect = TRUE)
    par(mar = c(5, 0, 0, 5))
    image(1:ncol(x), 1:nrow(x), t(x), axes = FALSE, xlim = c(0.5, 
        ncol(x) + 0.5), ylim = c(0.5, nrow(x) + 0.5), xlab = "", 
        ylab = "", ...)
    axis(1, 1:ncol(x), las = 2, line = -0.5, tick = 0, labels = if
(is.null(colnames(x))) 
        (1:ncol(x))[c.hc$order]
    else colnames(x), cex.axis = c.cex)
    axis(4, 1:nrow(x), las = 2, line = -0.5, tick = 0, labels = if
(is.null(rownames(x))) 
        (1:nrow(x))[r.hc$order]
    else rownames(x), cex.axis = r.cex)
    if (!missing(add.expr)) 
        eval(substitute(add.expr))
    par(mar = c(5, 3, 0, 0))
    plot(as.dendrogram(r.hc), horiz = TRUE, axes = FALSE, yaxs = "i")
    par(mar = c(0, 0, 3, 5))
    plot(as.dendrogram(c.hc), axes = FALSE, xaxs = "i")
    invisible(NULL)
}


> -----Original Message-----
> From: rossini@blindglobe.net [mailto:rossini@blindglobe.net]
> Sent: Friday, February 21, 2003 5:03 PM
> To: Liaw, Andy
> Cc: 'bioconductor@stat.math.ethz.ch'
> Subject: Re: [BioC] heatmap
> 
> 
> "Liaw, Andy" <andy_liaw@merck.com> writes:
> 
> 
> > The wisdom of looking at such a thing aside, has anyone implemented 
> > `heatmap' in R?  (That's the one where the data matrix is
> shown in a color
> > image, with dendrograms on the top and left sides of it
> indicating the
> > clustering of rows and columns.)
> >
> > I tried looking for it on the BioConductor website but
> didn't see any, so I
> > went ahead and whipped up a heatmap function to do it.  If anyone is

> > interested, let me know.
> 
> I'm interested...  ideally, you'd have the 2-way heat map (i.e. gene 
> and experiment clusters) but that is another story... (gosh, and I'd 
> be asking for alot, eh?)
> 
> best,
> -tony
> 
> -- 
> A.J. Rossini				Rsrch. Asst. Prof. of 
> Biostatistics
> U. of Washington Biostatistics		
> rossini@u.washington.edu	
> FHCRC/SCHARP/HIV Vaccine Trials Net	rossini@scharp.org
> -------------- http://software.biostat.washington.edu/
> ----------------
> FHCRC: M: 206-667-7025 (fax=4812)|Voicemail is pretty 
> sketchy/use Email
> UW:   Th: 206-543-1044 (fax=3286)|Change last 4 digits of phone to FAX
> (my tuesday/wednesday/friday locations are completely unpredictable.)
> 



------------------------------------------------------------------------
------


========================================================================
======