[BioC] colors on heatmap
Jean Yee Hwa Yang
jean at biostat.ucsf.edu
Fri Sep 12 15:52:28 MEST 2003
Hi all,
This is the similar to the function "maPalette" in the library marrayPlots.
Cheers
Jean
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Jean Yee Hwa Yang jean at biostat.ucsf.edu
Division of Biostatistics, Tel: (415) 476-3368
University of California, Fax: (415) 476-6014
500 Parnassus Avenue, MU 420-W, San Francisco, CA 94143-0560
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
On Fri, 12 Sep 2003, Warnes, Gregory R wrote:
>
> In the next release of the gregmisc packages I'll be including a couple of
> functions to make colorizing heatmaps easier. (As well as an enhanced
> heatmap function.)
>
> First the code:
>
>
> # detect odd/even integers
> odd <- function(x) x!=as.integer(x/2)*2
> even <- function(x) x==as.integer(x/2)*2
>
> # Generat a set of n colors which smoothly transition from 'low' to 'mid' to
> 'high'.
> colorpanel <- function(n,low='green',mid='black',high='red')
> {
> if(even(n)) warning("n is even: colors panel will not be symmetric")
>
> # convert to rgb
> low <- col2rgb(low)
> mid <- col2rgb(mid)
> high <- col2rgb(high)
>
> # determine length of each component
> lower <- floor(n/2)
> upper <- n - lower
>
> red <- c(
> seq(low[1,1], mid [1,1], length=lower),
> seq(mid[1,1], high[1,1], length=upper)
> )/255
>
> green <- c(
> seq(low[3,1], mid [3,1], length=lower),
> seq(mid[3,1], high[3,1], length=upper)
> )/255
>
> blue <- c(
> seq(low[2,1], mid [2,1], length=lower),
> seq(mid[2,1], high[2,1], length=upper)
> )/255
>
>
> rgb(red,blue,green)
> }
>
>
>
> # Generate red-black-green colorscale
> redgreen <- function(n) colorpanel(n, 'red', 'black', 'green')
>
> # Generate green-black-red colorscale
> greenred <- function(n) colorpanel(n, 'green', 'black', 'red' )
>
> # Generate blue white red colorscale
> bluered <- function(n) colorpanel(n, 'blue','white','red')
>
> ----
>
> The use is straightforward. To colorize a heatmap green-black-red, simply
> do:
>
> x <- matrix(runif(1000), 50, 20)
> hv <- heatmap(x, col = redgreen(32))
>
> -Greg
>
>
> > -----Original Message-----
> > From: Johannes Freudenberg [mailto:mai98ftu at studserv.uni-leipzig.de]
> > Sent: Friday, September 12, 2003 1:16 PM
> > To: Sean Davis
> > Cc: Bioconductor at stat.math.ethz.ch
> > Subject: Re: [BioC] colors on heatmap
> >
> >
> > Sean,
> >
> > I'm not quite sure what the standard green/black/red color
> > map is but i'm
> > assuming that green means low values, red means high values
> > and black is in the
> > middle?
> >
> > You could define a function which returns colors following
> > that scheme as
> > follows:
> >
> > > my.colors <- function(n = 50, low.col = 0.45, high.col=1,
> > saturation = 1) {
> > if (n < 2) stop("n must be greater than 2")
> > n1 <- n%/%2
> > n2 <- n - n1
> > c(hsv(low.col, saturation, seq(1,0,length=n1)),
> > hsv(high.col, saturation, seq(0,1,length=n2)))
> > }
> >
> > You could then use this function within the heatmap function:
> >
> > > x <- matrix(runif(1000), 50)
> > > hv <- heatmap(x, col = my.colors(), main = "Random U[0,1] heatmap")
> >
> > I hope that helps,
> > Johannes
> >
> >
> > Quoting Sean Davis <Sean.Davis at dcb.cit.nih.gov>:
> >
> > > I would like to use "heatmap" to display my data and
> > wondered if anyone
> > > had any suggestions on making a color scheme that works to
> > create the
> > > standard green/black/red color map.
> > >
> > > Thanks
> > >
> > > _______________________________________________
> > > Bioconductor mailing list
> > > Bioconductor at stat.math.ethz.ch
> > > https://www.stat.math.ethz.ch/mailman/listinfo/bioconductor
> > >
> >
> > _______________________________________________
> > Bioconductor mailing list
> > Bioconductor at stat.math.ethz.ch
> > https://www.stat.math.ethz.ch/mailman/listinfo/bioconductor
> >
>
>
> LEGAL NOTICE\ Unless expressly stated otherwise, this messag...{{dropped}}
>
> _______________________________________________
> Bioconductor mailing list
> Bioconductor at stat.math.ethz.ch
> https://www.stat.math.ethz.ch/mailman/listinfo/bioconductor
>
More information about the Bioconductor
mailing list