Thread: [R-gregmisc-users] SF.net SVN: r-gregmisc:[1323] trunk/gplots/R/heatmap.2.R
Brought to you by:
warnes
From: <wa...@us...> - 2009-05-08 22:51:25
|
Revision: 1323 http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1323&view=rev Author: warnes Date: 2009-05-08 22:51:07 +0000 (Fri, 08 May 2009) Log Message: ----------- heatmap.2: handle NA for RowV or ColV the same way as NULL Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2009-05-08 22:35:25 UTC (rev 1322) +++ trunk/gplots/R/heatmap.2.R 2009-05-08 22:51:07 UTC (rev 1323) @@ -103,9 +103,9 @@ ## key=FALSE ## } - if ( is.null(Rowv) ) + if ( is.null(Rowv) || is.na(Rowv) ) Rowv <- FALSE - if ( is.null(Colv) ) + if ( is.null(Colv) || is.na(Colv) ) Colv <- FALSE else if( Colv=="Rowv" && !isTRUE(Rowv) ) Colv <- FALSE This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2009-10-22 20:31:58
|
Revision: 1362 http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1362&view=rev Author: warnes Date: 2009-10-22 20:31:50 +0000 (Thu, 22 Oct 2009) Log Message: ----------- Fix transposed display of data (but not labels) in heatmap.2 when symm=TRUE Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2009-10-12 13:26:35 UTC (rev 1361) +++ trunk/gplots/R/heatmap.2.R 2009-10-22 20:31:50 UTC (rev 1362) @@ -354,11 +354,11 @@ } ## draw the main carpet par(mar = c(margins[1], 0, 0, margins[2])) - if(!symm || scale != "none") - { - x <- t(x) - cellnote <- t(cellnote) - } + #if(scale != "none" || !symm) + # { + # x <- t(x) + # cellnote <- t(cellnote) + # } if(revC) { ## x columns reversed iy <- nr:1 This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2009-10-22 20:53:19
|
Revision: 1364 http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1364&view=rev Author: warnes Date: 2009-10-22 20:53:11 +0000 (Thu, 22 Oct 2009) Log Message: ----------- Fixed typo in bug fix. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2009-10-22 20:37:49 UTC (rev 1363) +++ trunk/gplots/R/heatmap.2.R 2009-10-22 20:53:11 UTC (rev 1364) @@ -356,8 +356,8 @@ par(mar = c(margins[1], 0, 0, margins[2])) #if(scale != "none" || !symm) # { - # x <- t(x) - # cellnote <- t(cellnote) + x <- t(x) + cellnote <- t(cellnote) # } if(revC) { ## x columns reversed This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2010-12-13 16:44:24
|
Revision: 1463 http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1463&view=rev Author: warnes Date: 2010-12-13 16:44:17 +0000 (Mon, 13 Dec 2010) Log Message: ----------- Correct error that arises when data includes NA values, identified by Melissa Key Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2010-11-12 19:14:06 UTC (rev 1462) +++ trunk/gplots/R/heatmap.2.R 2010-12-13 16:44:17 UTC (rev 1463) @@ -493,8 +493,8 @@ { max.raw <- max(abs(c(x,breaks)),na.rm=TRUE) min.raw <- -max.raw - tmpbreaks[1] <- -max(abs(x)) - tmpbreaks[length(tmpbreaks)] <- max(abs(x)) + tmpbreaks[1] <- -max(abs(x), na.rm=TRUE) + tmpbreaks[length(tmpbreaks)] <- max(abs(x), na.rm=TRUE) } else { This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-04-04 21:32:57
|
Revision: 1778 http://sourceforge.net/p/r-gregmisc/code/1778 Author: warnes Date: 2014-04-04 21:32:51 +0000 (Fri, 04 Apr 2014) Log Message: ----------- Fix handling of row trace (hline). Bug report and patch provided by Ilia Kats. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-03-19 10:04:49 UTC (rev 1777) +++ trunk/gplots/R/heatmap.2.R 2014-04-04 21:32:51 UTC (rev 1778) @@ -86,9 +86,9 @@ x <- (x-low)/(high - low) x } - + retval <- list() - + scale <- if(symm && missing(scale)) "none" else match.arg(scale) dendrogram <- match.arg(dendrogram) trace <- match.arg(trace) @@ -115,8 +115,8 @@ Colv <- FALSE else if( Colv=="Rowv" && !isTRUE(Rowv) ) Colv <- FALSE - - + + if(length(di <- dim(x)) != 2 || !is.numeric(x)) stop("`x' must be a numeric matrix") @@ -141,10 +141,10 @@ dendrogram <- "column" else dedrogram <- "none" - + warning("Discrepancy: Rowv is FALSE, while dendrogram is `", dendrogram, "'. Omitting row dendogram.") - + } } @@ -157,13 +157,13 @@ dendrogram <- "row" else dendrogram <- "none" - + warning("Discrepancy: Colv is FALSE, while dendrogram is `", dendrogram, "'. Omitting column dendogram.") } } - - + + ## by default order by row/col mean ## if(is.null(Rowv)) Rowv <- rowMeans(x, na.rm = na.rm) ## if(is.null(Colv)) Colv <- colMeans(x, na.rm = na.rm) @@ -175,32 +175,32 @@ if(inherits(Rowv, "dendrogram")) { ddr <- Rowv ## use Rowv 'as-is', when it is dendrogram - rowInd <- order.dendrogram(ddr) + rowInd <- order.dendrogram(ddr) } else if (is.integer(Rowv)) { ## Compute dendrogram and do reordering based on given vector hcr <- hclustfun(distfun(x)) ddr <- as.dendrogram(hcr) ddr <- reorder(ddr, Rowv) - + rowInd <- order.dendrogram(ddr) if(nr != length(rowInd)) stop("row dendrogram ordering gave index of wrong length") } - else if (isTRUE(Rowv)) + else if (isTRUE(Rowv)) { ## If TRUE, compute dendrogram and do reordering based on rowMeans Rowv <- rowMeans(x, na.rm = na.rm) hcr <- hclustfun(distfun(x)) ddr <- as.dendrogram(hcr) ddr <- reorder(ddr, Rowv) - + rowInd <- order.dendrogram(ddr) if(nr != length(rowInd)) stop("row dendrogram ordering gave index of wrong length") } else { rowInd <- nr:1 } - + ## if( dendrogram %in% c("both","column") ) ## { if(inherits(Colv, "dendrogram")) @@ -247,7 +247,7 @@ retval$colInd <- colInd retval$call <- match.call() - + ## reorder x & cellnote x <- x[rowInd, colInd] x.unscaled <- x @@ -281,10 +281,10 @@ { if( missing(col) || is.function(col) ) breaks <- 16 - else + else breaks <- length(col)+1 } - + if(length(breaks)==1) { if(!symbreaks) @@ -308,7 +308,7 @@ x[x<min.breaks] <- min.breaks x[x>max.breaks] <- max.breaks - + ## Calculate the plot layout if( missing(lhei) || is.null(lhei) ) lhei <- c(keysize, 4) @@ -319,7 +319,7 @@ if( missing(lmat) || is.null(lmat) ) { lmat <- rbind(4:3, 2:1) - + if(!missing(ColSideColors)) { ## add middle row to layout if(!is.character(ColSideColors) || length(ColSideColors) != nc) stop("'ColSideColors' must be a character vector of length ncol(x)") @@ -336,7 +336,7 @@ lmat[is.na(lmat)] <- 0 } - + if(length(lhei) != nrow(lmat)) stop("lhei must have length = nrow(lmat) = ", nrow(lmat)) @@ -386,7 +386,7 @@ retval$colDendrogram <- ddc retval$breaks <- breaks retval$col <- col - + ## fill 'na' positions with na.color if(!invalid(na.color) & any(is.na(x))) { @@ -421,7 +421,7 @@ y=par("usr")[3] - (1.0 + offsetCol) * strheight("M"), labels=labCol, ##pos=1, - adj=adjCol, + adj=adjCol, cex=cexCol, srt=srtCol) par(xpd=xpd.orig) @@ -487,7 +487,7 @@ xright=nrow(x)+1, ytop = (ncol(x)+1-rsep)-0.5 - sepwidth[2], lty=1, lwd=1, col=sepcolor, border=sepcolor) - + ## show traces min.scale <- min(breaks) max.scale <- max(breaks) @@ -510,7 +510,7 @@ } } - + if(trace %in% c("both","row") ) { retval$hline <- hline @@ -519,7 +519,7 @@ { if(!is.null(hline)) { - abline(h=i + hline, col=linecol, lty=2) + abline(h=i - 0.5 + hline.vals, col=linecol, lty=2) } yv <- rep(i, ncol(x.scaled)) + x.scaled[i,] - 0.5 yv <- rev(c(yv[1], yv)) @@ -573,7 +573,7 @@ } else { - min.raw <- min(x, na.rm=TRUE) ## Again, modified to use scaled + min.raw <- min(x, na.rm=TRUE) ## Again, modified to use scaled max.raw <- max(x, na.rm=TRUE) ## or unscaled (SD 12/2/03) } @@ -595,12 +595,11 @@ if(density.info=="density") { - ## Experimental : also plot density of data dens <- density(x, adjust=densadj, na.rm=TRUE) omit <- dens$x < min(breaks) | dens$x > max(breaks) dens$x <- dens$x[-omit] dens$y <- dens$y[-omit] - dens$x <- scale01(dens$x,min.raw,max.raw) + dens$x <- scale01(dens$x, min.raw, max.raw) lines(dens$x, dens$y / max(dens$y) * 0.95, col=denscol, lwd=1) axis(2, at=pretty(dens$y)/max(dens$y) * 0.95, pretty(dens$y) ) title("Color Key\nand Density Plot") @@ -610,7 +609,7 @@ else if(density.info=="histogram") { h <- hist(x, plot=FALSE, breaks=breaks) - hx <- scale01(breaks,min.raw,max.raw) + hx <- scale01(breaks, min.raw, max.raw) hy <- c(h$counts, h$counts[length(h$counts)]) lines(hx, hy/max(hy)*0.95, lwd=1, type="s", col=denscol) axis(2, at=pretty(hy)/max(hy) * 0.95, pretty(hy) ) @@ -621,6 +620,30 @@ else title("Color Key") + + if(trace %in% c("both","column") ) + { + vline.vals <- scale01(vline, min.raw, max.raw) + if(!is.null(vline)) + { + abline(v=vline.vals, col=linecol, lty=2) + } + } + + + if(trace %in% c("both","row") ) + { + hline.vals <- scale01(hline, min.raw, max.raw) + if(!is.null(hline)) + { + abline(v=hline.vals, col=linecol, lty=2) + + } + } + + + + } else plot.new() @@ -630,8 +653,8 @@ low=retval$breaks[-length(retval$breaks)], high=retval$breaks[-1], color=retval$col - ) + ) - + invisible( retval ) } This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-04-09 23:52:19
|
Revision: 1802 http://sourceforge.net/p/r-gregmisc/code/1802 Author: warnes Date: 2014-04-09 23:52:17 +0000 (Wed, 09 Apr 2014) Log Message: ----------- Add padj=0.5 to better align margin labels. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-04-05 21:08:41 UTC (rev 1801) +++ trunk/gplots/R/heatmap.2.R 2014-04-09 23:52:17 UTC (rev 1802) @@ -66,6 +66,12 @@ denscol=tracecol, symkey = min(x < 0, na.rm=TRUE) || symbreaks, densadj = 0.25, + key.title = NULL, + key.xlab = NULL, + key.ylab = NULL, + key.xtickfun = NULL, + key.ytickfun = NULL, + key.par=list(), ## plot labels main = NULL, @@ -562,7 +568,16 @@ ## Add the color-key if(key) { - par(mar = c(5, 4, 2, 1), cex=0.75) + mar <- c(5, 4, 2, 1) + if (!is.null(key.xlab) && is.na(key.xlab)) + mar[1] <- 2 + if (!is.null(key.ylab) && is.na(key.ylab)) + mar[2] <- 2 + if (!is.null(key.title) && is.na(key.title)) + mar[3] <- 1 + par(mar = mar, cex=0.75, mgp=c(2, 1, 0)) + if (length(key.par) > 0) + do.call(par, key.par) tmpbreaks <- breaks if(symkey) @@ -584,15 +599,26 @@ xaxt="n", yaxt="n") par(usr=c(0,1,0,1)) - lv <- pretty(breaks) - xv <- scale01(as.numeric(lv), min.raw, max.raw) - axis(1, at=xv, labels=lv) - if(scale=="row") - mtext(side=1,"Row Z-Score", line=2) - else if(scale=="column") - mtext(side=1,"Column Z-Score", line=2) - else - mtext(side=1,"Value", line=2) + if (is.null(key.xtickfun)) { + lv <- pretty(breaks) + xv <- scale01(as.numeric(lv), min.raw, max.raw) + xargs <- list(at=xv, labels=lv) + } else { + xargs <- key.xtickfun() + } + xargs$side <- 1 + do.call(axis, xargs) + if (is.null(key.xlab)) { + if(scale=="row") + key.xlab <- "Row Z-Score" + else if(scale=="column") + key.xlab <- "Column Z-Score" + else + key.xlab <- "Value" + } + if (!is.na(key.xlab)) { + mtext(side=1, key.xlab, line=par("mgp")[1], padj=0.5) + } if(density.info=="density") { @@ -602,10 +628,22 @@ dens$y <- dens$y[-omit] dens$x <- scale01(dens$x, min.raw, max.raw) lines(dens$x, dens$y / max(dens$y) * 0.95, col=denscol, lwd=1) - axis(2, at=pretty(dens$y)/max(dens$y) * 0.95, pretty(dens$y) ) - title("Color Key\nand Density Plot") + if (is.null(key.ytickfun)) { + yargs <- list(at=pretty(dens$y)/max(dens$y) * 0.95, labels=pretty(dens$y)) + } else { + yargs <- key.ytickfun() + } + yargs$side <- 2 + do.call(axis, yargs) + if (is.null(key.title)) + key.title <- "Color Key\nand Density Plot" + if (!is.na(key.title)) + title(key.title) par(cex=0.5) - mtext(side=2,"Density", line=2) + if (is.null(key.ylab)) + key.ylab <- "Density" + if (!is.na(key.ylab)) + mtext(side=2,key.ylab, line=par("mgp")[1], padj=0.5) } else if(density.info=="histogram") { @@ -613,10 +651,22 @@ hx <- scale01(breaks, min.raw, max.raw) hy <- c(h$counts, h$counts[length(h$counts)]) lines(hx, hy/max(hy)*0.95, lwd=1, type="s", col=denscol) - axis(2, at=pretty(hy)/max(hy) * 0.95, pretty(hy) ) - title("Color Key\nand Histogram") + if (is.null(key.ytickfun)) { + yargs <- list(at=pretty(hy)/max(hy) * 0.95, labels=pretty(hy)) + } else { + yargs <- key.ytickfun() + } + yargs$side <- 2 + do.call(axis, yargs) + if (is.null(key.title)) + key.title <- "Color Key\nand Histogram" + if (!is.na(key.title)) + title(key.title) par(cex=0.5) - mtext(side=2,"Count", line=2) + if (is.null(key.ylab)) + key.ylab <- "Count" + if (!is.na(key.ylab)) + mtext(side=2,key.ylab, line=par("mgp")[1], padj=0.5) } else title("Color Key") This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-06-05 17:21:17
|
Revision: 1817 http://sourceforge.net/p/r-gregmisc/code/1817 Author: warnes Date: 2014-06-05 17:21:11 +0000 (Thu, 05 Jun 2014) Log Message: ----------- Check size of Rowv and Colv dendogram objects to ensure they matches data. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-05-28 00:24:23 UTC (rev 1816) +++ trunk/gplots/R/heatmap.2.R 2014-06-05 17:21:11 UTC (rev 1817) @@ -183,6 +183,8 @@ { ddr <- Rowv ## use Rowv 'as-is', when it is dendrogram rowInd <- order.dendrogram(ddr) + if(length(rowInd)>nr || any(rowInd<1 | rowInd > nr )) + stop("Rowv dendrogram doesn't match size of x") } else if (is.integer(Rowv)) { ## Compute dendrogram and do reordering based on given vector @@ -214,6 +216,8 @@ { ddc <- Colv ## use Colv 'as-is', when it is dendrogram colInd <- order.dendrogram(ddc) + if(length(ColInd)>nr || any(colInd<1 | colInd > nc )) + stop("Colv dendrogram doesn't match size of x") } else if(identical(Colv, "Rowv")) { if(nr != nc) This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-06-17 20:34:24
|
Revision: 1818 http://sourceforge.net/p/r-gregmisc/code/1818 Author: warnes Date: 2014-06-17 20:34:17 +0000 (Tue, 17 Jun 2014) Log Message: ----------- Fix typo in heatmap.2() reported by Yuanhua Liu. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-06-05 17:21:11 UTC (rev 1817) +++ trunk/gplots/R/heatmap.2.R 2014-06-17 20:34:17 UTC (rev 1818) @@ -147,7 +147,7 @@ if (is.logical(Colv) && (Colv)) dendrogram <- "column" else - dedrogram <- "none" + dendrogram <- "none" warning("Discrepancy: Rowv is FALSE, while dendrogram is `", dendrogram, "'. Omitting row dendogram.") This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-06-17 23:19:50
|
Revision: 1819 http://sourceforge.net/p/r-gregmisc/code/1819 Author: warnes Date: 2014-06-17 23:19:46 +0000 (Tue, 17 Jun 2014) Log Message: ----------- Allow user to specify function used to reorder based on the dendogram via a new 'reorderfun' argument. Suggested by Yuanhua Liu. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-06-17 20:34:17 UTC (rev 1818) +++ trunk/gplots/R/heatmap.2.R 2014-06-17 23:19:46 UTC (rev 1819) @@ -8,6 +8,7 @@ distfun = dist, hclustfun = hclust, dendrogram = c("both","row","column","none"), + reorderfun = function(d, w) reorder(d, w), symm = FALSE, ## data scaling @@ -109,13 +110,6 @@ "specified can produce unpredictable results.", "Please consider using only one or the other.") - ## key & density don't make sense when data is not all on the same scale - ## if(scale!="none" && key==TRUE) - ## { - ## warning("Key cannot be plotted when scale!=\"none\".") - ## key=FALSE - ## } - if ( is.null(Rowv) || is.na(Rowv) ) Rowv <- FALSE if ( is.null(Colv) || is.na(Colv) ) @@ -190,7 +184,7 @@ { ## Compute dendrogram and do reordering based on given vector hcr <- hclustfun(distfun(x)) ddr <- as.dendrogram(hcr) - ddr <- reorder(ddr, Rowv) + ddr <- reorderfun(ddr, Rowv) rowInd <- order.dendrogram(ddr) if(nr != length(rowInd)) @@ -201,7 +195,7 @@ Rowv <- rowMeans(x, na.rm = na.rm) hcr <- hclustfun(distfun(x)) ddr <- as.dendrogram(hcr) - ddr <- reorder(ddr, Rowv) + ddr <- reorderfun(ddr, Rowv) rowInd <- order.dendrogram(ddr) if(nr != length(rowInd)) @@ -232,7 +226,7 @@ {## Compute dendrogram and do reordering based on given vector hcc <- hclustfun(distfun(if(symm)x else t(x))) ddc <- as.dendrogram(hcc) - ddc <- reorder(ddc, Colv) + ddc <- reorderfun(ddc, Colv) colInd <- order.dendrogram(ddc) if(nc != length(colInd)) @@ -243,7 +237,7 @@ Colv <- colMeans(x, na.rm = na.rm) hcc <- hclustfun(distfun(if(symm)x else t(x))) ddc <- as.dendrogram(hcc) - ddc <- reorder(ddc, Colv) + ddc <- reorderfun(ddc, Colv) colInd <- order.dendrogram(ddc) if(nc != length(colInd)) This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-06-19 18:51:40
|
Revision: 1822 http://sourceforge.net/p/r-gregmisc/code/1822 Author: warnes Date: 2014-06-19 18:51:32 +0000 (Thu, 19 Jun 2014) Log Message: ----------- Fix typo 'ColInd' --> 'colInd'. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-06-19 18:36:19 UTC (rev 1821) +++ trunk/gplots/R/heatmap.2.R 2014-06-19 18:51:32 UTC (rev 1822) @@ -210,7 +210,7 @@ { ddc <- Colv ## use Colv 'as-is', when it is dendrogram colInd <- order.dendrogram(ddc) - if(length(ColInd)>nr || any(colInd<1 | colInd > nc )) + if(length(colInd)>nr || any(colInd<1 | colInd > nc )) stop("Colv dendrogram doesn't match size of x") } else if(identical(Colv, "Rowv")) { This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-06-30 19:26:24
|
Revision: 1823 http://sourceforge.net/p/r-gregmisc/code/1823 Author: warnes Date: 2014-06-30 19:26:21 +0000 (Mon, 30 Jun 2014) Log Message: ----------- Fix typo in dendrogram size checking code. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-06-19 18:51:32 UTC (rev 1822) +++ trunk/gplots/R/heatmap.2.R 2014-06-30 19:26:21 UTC (rev 1823) @@ -210,7 +210,7 @@ { ddc <- Colv ## use Colv 'as-is', when it is dendrogram colInd <- order.dendrogram(ddc) - if(length(colInd)>nr || any(colInd<1 | colInd > nc )) + if(length(colInd)>nc || any(colInd<1 | colInd > nc )) stop("Colv dendrogram doesn't match size of x") } else if(identical(Colv, "Rowv")) { This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-09-17 13:53:42
|
Revision: 1889 http://sourceforge.net/p/r-gregmisc/code/1889 Author: warnes Date: 2014-09-17 13:53:34 +0000 (Wed, 17 Sep 2014) Log Message: ----------- key.title=NA was not being honored when density.info=NA. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-09-16 18:11:13 UTC (rev 1888) +++ trunk/gplots/R/heatmap.2.R 2014-09-17 13:53:34 UTC (rev 1889) @@ -667,7 +667,8 @@ mtext(side=2,key.ylab, line=par("mgp")[1], padj=0.5) } else - title("Color Key") + if (is.null(key.title)) + title("Color Key") if(trace %in% c("both","column") ) This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-09-17 21:34:37
|
Revision: 1890 http://sourceforge.net/p/r-gregmisc/code/1890 Author: warnes Date: 2014-09-17 21:34:28 +0000 (Wed, 17 Sep 2014) Log Message: ----------- heatmap.2 was not properly handling integer vectors for Rowv and Colv. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-09-17 13:53:34 UTC (rev 1889) +++ trunk/gplots/R/heatmap.2.R 2014-09-17 21:34:28 UTC (rev 1890) @@ -114,8 +114,8 @@ Rowv <- FALSE if ( is.null(Colv) || is.na(Colv) ) Colv <- FALSE - else if( Colv=="Rowv" && !isTRUE(Rowv) ) - Colv <- FALSE + else if( all(Colv=="Rowv") ) + Colv <- Rowv if(length(di <- dim(x)) != 2 || !is.numeric(x)) @@ -135,8 +135,15 @@ if(!inherits(Rowv, "dendrogram")) { ## Check if Rowv and dendrogram arguments are consistent - if ( ( (!isTRUE(Rowv)) || (is.null(Rowv))) && - (dendrogram %in% c("both","row") ) ) + if ( + ( + ( is.logical(Rowv) && !isTRUE(Rowv) ) + || + ( is.null(Rowv) ) + ) + && + ( dendrogram %in% c("both","row") ) + ) { if (is.logical(Colv) && (Colv)) dendrogram <- "column" @@ -151,8 +158,14 @@ if(!inherits(Colv, "dendrogram")) { ## Check if Colv and dendrogram arguments are consistent - if ( ( (!isTRUE(Colv)) || (is.null(Colv))) - && (dendrogram %in% c("both","column")) ) + if ( + ( + (is.logical(Colv) && !isTRUE(Colv) ) + || + (is.null(Colv)) + ) + && + ( dendrogram %in% c("both","column")) ) { if (is.logical(Rowv) && (Rowv)) dendrogram <- "row" @@ -182,9 +195,10 @@ } else if (is.integer(Rowv)) { ## Compute dendrogram and do reordering based on given vector + browser() hcr <- hclustfun(distfun(x)) ddr <- as.dendrogram(hcr) - ddr <- reorderfun(ddr, Rowv) + ddr <- reorderfun(ddr, Rowv) rowInd <- order.dendrogram(ddr) if(nr != length(rowInd)) This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-04-23 18:49:30
|
Revision: 1940 http://sourceforge.net/p/r-gregmisc/code/1940 Author: warnes Date: 2015-04-23 18:49:23 +0000 (Thu, 23 Apr 2015) Log Message: ----------- In heatmap.2() split calls to distfun() and hclustfun() into separate steps to make debugging easier Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2015-04-23 17:40:13 UTC (rev 1939) +++ trunk/gplots/R/heatmap.2.R 2015-04-23 18:49:23 UTC (rev 1940) @@ -198,7 +198,8 @@ else if (is.integer(Rowv)) { ## Compute dendrogram and do reordering based on given vector browser() - hcr <- hclustfun(distfun(x)) + distr <- distfun(x) + hcr <- hclustfun(distr) ddr <- as.dendrogram(hcr) ddr <- reorderfun(ddr, Rowv) @@ -209,7 +210,8 @@ else if (isTRUE(Rowv)) { ## If TRUE, compute dendrogram and do reordering based on rowMeans Rowv <- rowMeans(x, na.rm = na.rm) - hcr <- hclustfun(distfun(x)) + distr <- distfun(x) + hcr <- hclustfun(distr) ddr <- as.dendrogram(hcr) ddr <- reorderfun(ddr, Rowv) @@ -240,7 +242,8 @@ colInd <- rowInd } else if(is.integer(Colv)) {## Compute dendrogram and do reordering based on given vector - hcc <- hclustfun(distfun(if(symm)x else t(x))) + distc <- distfun(if(symm)x else t(x)) + hcc <- hclustfun(distc) ddc <- as.dendrogram(hcc) ddc <- reorderfun(ddc, Colv) @@ -251,7 +254,8 @@ else if (isTRUE(Colv)) {## If TRUE, compute dendrogram and do reordering based on rowMeans Colv <- colMeans(x, na.rm = na.rm) - hcc <- hclustfun(distfun(if(symm)x else t(x))) + distc <- distfun(if(symm)x else t(x)) + hcc <- hclustfun(distc) ddc <- as.dendrogram(hcc) ddc <- reorderfun(ddc, Colv) This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-04-23 19:09:24
|
Revision: 1941 http://sourceforge.net/p/r-gregmisc/code/1941 Author: warnes Date: 2015-04-23 19:09:17 +0000 (Thu, 23 Apr 2015) Log Message: ----------- Patch submitted by Ilia Kats: - easily extract and plot subclusters from a big heatmap using the same colorkey, by passing a dendgrogram of the subcluster together with the full data matrix and, optionally, the breaks of the full heatmap in order to obtain the same color scaling. This is useful if one wants to plot several subclusters as different panels in a paper, but maintain consistent color coding. - Improves the behavior of the color key axis labels, as they now honor par("cex") and par("cex.lab"). Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2015-04-23 18:49:23 UTC (rev 1940) +++ trunk/gplots/R/heatmap.2.R 2015-04-23 19:09:17 UTC (rev 1941) @@ -194,6 +194,8 @@ rowInd <- order.dendrogram(ddr) if(length(rowInd)>nr || any(rowInd<1 | rowInd > nr )) stop("Rowv dendrogram doesn't match size of x") + if (length(rowInd) < nr) + nr <- length(rowInd) } else if (is.integer(Rowv)) { ## Compute dendrogram and do reordering based on given vector @@ -230,6 +232,8 @@ colInd <- order.dendrogram(ddc) if(length(colInd)>nc || any(colInd<1 | colInd > nc )) stop("Colv dendrogram doesn't match size of x") + if (length(colInd) < nc) + nc <- length(colInd) } else if(identical(Colv, "Rowv")) { if(nr != nc) @@ -633,8 +637,8 @@ } else { - min.raw <- min(x, na.rm=TRUE) ## Again, modified to use scaled - max.raw <- max(x, na.rm=TRUE) ## or unscaled (SD 12/2/03) + min.raw <- min.breaks + max.raw <- max.breaks } z <- seq(min.raw, max.raw, length=length(col)) @@ -661,7 +665,7 @@ key.xlab <- "Value" } if (!is.na(key.xlab)) { - mtext(side=1, key.xlab, line=par("mgp")[1], padj=0.5) + mtext(side=1, key.xlab, line=par("mgp")[1], padj=0.5, cex=par("cex") * par("cex.lab")) } if(density.info=="density") @@ -687,7 +691,7 @@ if (is.null(key.ylab)) key.ylab <- "Density" if (!is.na(key.ylab)) - mtext(side=2,key.ylab, line=par("mgp")[1], padj=0.5) + mtext(side=2,key.ylab, line=par("mgp")[1], padj=0.5, cex=par("cex") * par("cex.lab")) } else if(density.info=="histogram") { @@ -710,7 +714,7 @@ if (is.null(key.ylab)) key.ylab <- "Count" if (!is.na(key.ylab)) - mtext(side=2,key.ylab, line=par("mgp")[1], padj=0.5) + mtext(side=2,key.ylab, line=par("mgp")[1], padj=0.5, cex=par("cex") * par("cex.lab")) } else if (is.null(key.title)) This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-05-01 15:28:36
|
Revision: 1995 http://sourceforge.net/p/r-gregmisc/code/1995 Author: warnes Date: 2015-05-01 15:28:33 +0000 (Fri, 01 May 2015) Log Message: ----------- - heatmap.2: row traces could be plotted in the wrong order. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2015-05-01 15:25:31 UTC (rev 1994) +++ trunk/gplots/R/heatmap.2.R 2015-05-01 15:28:33 UTC (rev 1995) @@ -554,7 +554,7 @@ { retval$hline <- hline hline.vals <- scale01(hline, min.scale, max.scale) - for( i in rowInd ) + for( i in 1:length(rowInd) ) { if(!is.null(hline)) { This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |