Thread: [R-gregmisc-users] SF.net SVN: r-gregmisc:[1673] trunk/gplots (Page 2)
Brought to you by:
warnes
From: <wa...@us...> - 2013-06-27 20:20:48
|
Revision: 1673 http://sourceforge.net/p/r-gregmisc/code/1673 Author: warnes Date: 2013-06-27 20:20:46 +0000 (Thu, 27 Jun 2013) Log Message: ----------- Modify sinkplot to use a local environement to store its information instead of the global environment. Modified Paths: -------------- trunk/gplots/R/sinkplot.R trunk/gplots/man/sinkplot.Rd Modified: trunk/gplots/R/sinkplot.R =================================================================== --- trunk/gplots/R/sinkplot.R 2013-06-14 20:58:06 UTC (rev 1672) +++ trunk/gplots/R/sinkplot.R 2013-06-27 20:20:46 UTC (rev 1673) @@ -1,18 +1,19 @@ # $Id$ - +sinkplotEnv <-new.env() + sinkplot <- function(operation=c("start","plot","cancel"),...) { operation <- match.arg(operation) if( operation=="start" ) { - if (exists(".sinkplot.conn", envir=globalenv()) && - get(".sinkplot.conn", envir=globalenv()) ) + if (exists(".sinkplot.conn", envir=sinkplotEnv) && + get(".sinkplot.conn", envir=sinkplotEnv) ) stop("sinkplot already in force") .sinkplot.conn <- textConnection(".sinkplot.data", "w", local=FALSE) - assign(x=".sinkplot.conn", value=.sinkplot.conn, envir=globalenv()) + assign(x=".sinkplot.conn", value=.sinkplot.conn, envir=sinkplotEnv) on.exit(sink()) sink(.sinkplot.conn) @@ -20,23 +21,24 @@ } else { - if (!exists(".sinkplot.conn", envir=globalenv()) || !.sinkplot.conn ) + if (!exists(".sinkplot.conn", envir=sinkplotEnv) || + !get(".sinkplot.conn", envir=sinkplotEnv) ) stop("No sinkplot currently in force") sink() - data <- get(".sinkplot.data", envir=globalenv()) + data <- get(".sinkplot.data", envir=sinkplotEnv) if( operation=="plot" ) textplot( paste( data, collapse="\n"), ... ) - close(get(".sinkplot.conn", envir=globalenv())) + close(get(".sinkplot.conn", envir=sinkplotEnv)) - if(exists(".sinkplot.data", envir=globalenv())) - rm(".sinkplot.data", pos=globalenv()) + if(exists(".sinkplot.data", envir=sinkplotEnv, inherits=FALSE)) + rm(list=".sinkplot.data", pos=sinkplotEnv, inherits=FALSE) - if(exists(".sinkplot.conn", envir=globalenv())) - rm(".sinkplot.conn", pos=globalenv()) + if(exists(".sinkplot.conn", envir=sinkplotEnv, inherits=FALSE)) + rm(list=".sinkplot.conn", pos=sinkplotEnv, inherits=FALSE) invisible(data) } Modified: trunk/gplots/man/sinkplot.Rd =================================================================== --- trunk/gplots/man/sinkplot.Rd 2013-06-14 20:58:06 UTC (rev 1672) +++ trunk/gplots/man/sinkplot.Rd 2013-06-27 20:20:46 UTC (rev 1673) @@ -35,18 +35,18 @@ \author{ Gregory R. Warnes \email{gr...@wa...} } \seealso{ \code{\link[utils]{capture.output}}, \code{\link{textplot}} } \examples{ -\dontrun{ set.seed(12456) x <- factor(sample( LETTERS[1:5], 50, replace=TRUE)) y <- rnorm(50, mean=as.numeric(x), sd=1) + ## construct a figure showing a box plot of the data, followed by an + ## analysis of variance table for the data + layout(cbind(1:2), heights=c(2,1)) - par(mfrow=c(1,2)) boxplot(y~x, col="darkgreen") sinkplot() anova(lm(y~x)) sinkplot("plot",col="darkgreen") } -} \keyword{hplot} This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2013-10-11 20:19:25
|
Revision: 1724 http://sourceforge.net/p/r-gregmisc/code/1724 Author: warnes Date: 2013-10-11 20:19:22 +0000 (Fri, 11 Oct 2013) Log Message: ----------- Add parameters to control row and column label positioning, rotation, justification, and offset. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R trunk/gplots/man/heatmap.2.Rd Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2013-10-11 17:15:54 UTC (rev 1723) +++ trunk/gplots/R/heatmap.2.R 2013-10-11 20:19:22 UTC (rev 1724) @@ -52,6 +52,12 @@ cexCol = 0.2 + 1/log10(nc), labRow = NULL, labCol = NULL, + srtRow = NULL, + srtCol = NULL, + adjRow = c(0,NA), + adjCol = c(NA,0), + offsetRow = 0.5, + offsetCol = 0.5, ## color key + density info key = TRUE, @@ -389,10 +395,79 @@ col=na.color, add=TRUE) } - ## add labels - axis(1, 1:nc, labels= labCol, las= 2, line= -0.5, tick= 0, cex.axis= cexCol) + ## add column labels + if(is.null(srtCol)) + axis(1, + 1:nc, + labels= labCol, + las= 2, + line= -0.5 + offsetCol, + tick= 0, + cex.axis= cexCol, + hadj=adjCol[1], + padj=adjCol[2] + ) + else + { + if(is.numeric(srtCol)) + { + if(missing(adjCol) || is.null(adjCol)) + adjCol=c(1,NA) + + xpd.orig <- par("xpd") + par(xpd=NA) + xpos <- axis(1, 1:nc, labels=rep("", nc), las=2, tick=0) + text(x=xpos, + y=par("usr")[3] - (1.0 + offsetCol) * strheight("M"), + labels=labCol, + ##pos=1, + adj=adjCol, + cex=cexCol, + srt=srtCol) + par(xpd=xpd.orig) + } + else + warning("Invalid value for srtCol ignored.") + } + + ## add row labels + if(is.null(srtRow)) + { + axis(4, + iy, + labels=labRow, + las=2, + line=-0.5+offsetRow, + tick=0, + cex.axis=cexRow, + hadj=adjRow[1], + padj=adjRow[2] + ) + } + else + { + if(is.numeric(srtRow)) + { + xpd.orig <- par("xpd") + par(xpd=NA) + ypos <- axis(4, iy, labels=rep("", nr), las=2, line= -0.5, tick=0) + text(x=par("usr")[2] + (1.0 + offsetRow) * strwidth("M"), + y=ypos, + labels=labRow, + adj=adjRow, + cex=cexRow, + srt=srtRow + ) + par(xpd=xpd.orig) + } + else + warning("Invalid value for srtRow ignored.") + } + + + + ## add row and column headings (xlab, ylab) if(!is.null(xlab)) mtext(xlab, side = 1, line = margins[1] - 1.25) - axis(4, iy, labels= labRow, las= 2, line= -0.5, tick= 0, cex.axis= cexRow) if(!is.null(ylab)) mtext(ylab, side = 4, line = margins[2] - 1.25) ## perform user-specified function Modified: trunk/gplots/man/heatmap.2.Rd =================================================================== --- trunk/gplots/man/heatmap.2.Rd 2013-10-11 17:15:54 UTC (rev 1723) +++ trunk/gplots/man/heatmap.2.Rd 2013-10-11 20:19:22 UTC (rev 1724) @@ -64,6 +64,12 @@ cexCol = 0.2 + 1/log10(nc), labRow = NULL, labCol = NULL, + srtRow = NULL, + srtCol = NULL, + adjRow = c(0,NA), + adjCol = c(NA,0), + offsetRow = 0.5, + offsetCol = 0.5, # color key + density info key = TRUE, @@ -178,6 +184,12 @@ \item{labRow, labCol}{character vectors with row and column labels to use; these default to \code{rownames(x)} or \code{colnames(x)}, respectively.} + \item{srtRow, srtCol}{angle of row/column labels, in degrees from horizontal} + \item{adjRow, adjCol}{2-element vector giving the (left-right, + top-bottom) justification of row/column labels (relative to the text + orientation).} + \item{offsetRow, offsetCol}{Number of character-width spaces to place + between row/column labels and the edge of the plotting region.} % Color key and density info \item{key}{logical indicating whether a color-key should be shown.} \item{keysize}{numeric value indicating the size of the key} @@ -302,6 +314,33 @@ heatmap.2(x, Rowv=NULL, dendrogram="both") ## generate warning! heatmap.2(x, Colv=FALSE, dendrogram="both") ## generate warning! + ## Show effect of row and column label rotation + heatmap.2(x, srtCol=NULL) + heatmap.2(x, srtCol=0, adjCol = c(0.5,1) ) + heatmap.2(x, srtCol=45, adjCol = c(1,1) ) + heatmap.2(x, srtCol=135, adjCol = c(1,0) ) + heatmap.2(x, srtCol=180, adjCol = c(0.5,0) ) + heatmap.2(x, srtCol=225, adjCol = c(0,0) ) ## not very useful + heatmap.2(x, srtCol=270, adjCol = c(0,0.5) ) + heatmap.2(x, srtCol=315, adjCol = c(0,1) ) + heatmap.2(x, srtCol=360, adjCol = c(0.5,1) ) + + heatmap.2(x, srtRow=45, adjRow=c(0, 1) ) + heatmap.2(x, srtRow=45, adjRow=c(0, 1), srtCol=45, adjCol=c(1,1) ) + heatmap.2(x, srtRow=45, adjRow=c(0, 1), srtCol=270, adjCol=c(0,0.5) ) + + ## Show effect of offsetRow/offsetCol (only works when srtRow/srtCol is + ## not also present) + heatmap.2(x, offsetRow=0, offsetCol=0) + heatmap.2(x, offsetRow=1, offsetCol=1) + heatmap.2(x, offsetRow=2, offsetCol=2) + heatmap.2(x, offsetRow=-1, offsetCol=-1) + + heatmap.2(x, srtRow=0, srtCol=90, offsetRow=0, offsetCol=0) + heatmap.2(x, srtRow=0, srtCol=90, offsetRow=1, offsetCol=1) + heatmap.2(x, srtRow=0, srtCol=90, offsetRow=2, offsetCol=2) + heatmap.2(x, srtRow=0, srtCol=90, offsetRow=-1, offsetCol=-1) + ## ## Show effect of z-score scaling within columns, blue-red color scale ## This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2013-10-11 20:24:37
|
Revision: 1725 http://sourceforge.net/p/r-gregmisc/code/1725 Author: warnes Date: 2013-10-11 20:24:34 +0000 (Fri, 11 Oct 2013) Log Message: ----------- Update files for gplots 2.12.0 Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2013-10-11 20:19:22 UTC (rev 1724) +++ trunk/gplots/DESCRIPTION 2013-10-11 20:24:34 UTC (rev 1725) @@ -3,13 +3,13 @@ Description: Various R programming tools for plotting data Depends: R (>= 3.0), gtools, gdata, stats, caTools, grid, KernSmooth, MASS, datasets -Recommends: grid -Suggests: gtools -Version: 2.11.3 -Date: 2013-06-27 +Suggests: gtools, grid +Version: 2.12.0 +Date: 2013-10-11 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Venables Maintainer: Gregory R. Warnes <gr...@wa...> License: GPL-2 +NeedsCompilation: No Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2013-10-11 20:19:22 UTC (rev 1724) +++ trunk/gplots/inst/NEWS 2013-10-11 20:24:34 UTC (rev 1725) @@ -1,3 +1,18 @@ +Release 2.11.4 - 2013-10-11 +--------------------------- + +Enhancements: + +- Add heatmap.2() parameters to control row and column label rotation + ('srtRow', 'srtCol'), justification ('adjRow', 'adjCol'), and space + from plot edge ('offsetRow', 'offsetCol'). + +Bug Fixes: + +- Fix bug in venn diagram code when number of TRUE cases in each + variable are equal. + + Release 2.11.3 - 2013-06-27 --------------------------- This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2013-10-15 02:09:33
|
Revision: 1738 http://sourceforge.net/p/r-gregmisc/code/1738 Author: warnes Date: 2013-10-15 02:09:31 +0000 (Tue, 15 Oct 2013) Log Message: ----------- Rename boxplot.n to boxplt2 and plot.lm2 to lmplot2 Modified Paths: -------------- trunk/gplots/man/gplots-deprecated.Rd Added Paths: ----------- trunk/gplots/R/boxplot2.R trunk/gplots/R/lmplot2.R trunk/gplots/man/boxplot2.Rd trunk/gplots/man/lmplot2.Rd Removed Paths: ------------- trunk/gplots/R/boxplot.n.R trunk/gplots/R/plot.lm.R trunk/gplots/man/boxplot.n.Rd trunk/gplots/man/boxplot2.Rd trunk/gplots/man/lmplot2.Rd trunk/gplots/man/plot.lm2.Rd Deleted: trunk/gplots/R/boxplot.n.R =================================================================== --- trunk/gplots/R/boxplot.n.R 2013-10-15 01:47:31 UTC (rev 1737) +++ trunk/gplots/R/boxplot.n.R 2013-10-15 02:09:31 UTC (rev 1738) @@ -1,52 +0,0 @@ -# $Id$ - -boxplot.n <- function( ..., top=FALSE, shrink=1.0, textcolor=NULL ) - { - boxcall <- match.call() # get call - boxcall$top <- boxcall$shrink <- boxcall$textcolor <- NULL - boxcall[[1]] <- as.name("boxplot") - - if(is.R()) - { - box <- eval(boxcall, parent.frame()) - mids <- 1:length(box$n) - } - else - { - mids <- eval(boxcall, parent.frame()) - boxcall$plot <- FALSE - box <- eval(boxcall, parent.frame()) - } - - if(top) - { - where <- par("usr")[4] - adj <- c(0.5,1) - } - else - { - where <- par("usr")[3] - adj <- c(0.5,0) - } - tcex <- par("cex") - par(cex=shrink*tcex) - - if(is.R()) - text( x=mids, y=where, labels=paste("n=",box$n,sep=""), adj=adj, - col=textcolor) - else - { - if( is.null(textcolor) ) - textcolor <- 1 - space <- ifelse(top, -1, 1) * par("1em")[2] / 2 - - text( x=mids, y=where + space, labels=paste("n=",box$n,sep=""), adj=adj[1], - col=textcolor) - - } - - par(cex=tcex) - - invisible(box) - } - Copied: trunk/gplots/R/boxplot2.R (from rev 1672, trunk/gplots/R/boxplot.n.R) =================================================================== --- trunk/gplots/R/boxplot2.R (rev 0) +++ trunk/gplots/R/boxplot2.R 2013-10-15 02:09:31 UTC (rev 1738) @@ -0,0 +1,60 @@ +# $Id$ +boxplot.n <- function( ..., top=FALSE, shrink=1.0, textcolor=NULL ) + { + .Deprecated("gboxplot", package="gplots") + cl <- match.call() + mf <- match.call(expand.dots = FALSE) + mf[[1L]] <- quote(boxplot2) + eval(mf, parent.frame()) + } + +boxplot2 <- function( ..., top=FALSE, shrink=1.0, textcolor=NULL ) + { + boxcall <- match.call() # get call + boxcall$top <- boxcall$shrink <- boxcall$textcolor <- NULL + boxcall[[1]] <- as.name("boxplot") + + if(is.R()) + { + box <- eval(boxcall, parent.frame()) + mids <- 1:length(box$n) + } + else + { + mids <- eval(boxcall, parent.frame()) + boxcall$plot <- FALSE + box <- eval(boxcall, parent.frame()) + } + + if(top) + { + where <- par("usr")[4] + adj <- c(0.5,1) + } + else + { + where <- par("usr")[3] + adj <- c(0.5,0) + } + tcex <- par("cex") + par(cex=shrink*tcex) + + if(is.R()) + text( x=mids, y=where, labels=paste("n=",box$n,sep=""), adj=adj, + col=textcolor) + else + { + if( is.null(textcolor) ) + textcolor <- 1 + space <- ifelse(top, -1, 1) * par("1em")[2] / 2 + + text( x=mids, y=where + space, labels=paste("n=",box$n,sep=""), adj=adj[1], + col=textcolor) + + } + + par(cex=tcex) + + invisible(box) + } + Copied: trunk/gplots/R/lmplot2.R (from rev 1672, trunk/gplots/R/plot.lm.R) =================================================================== --- trunk/gplots/R/lmplot2.R (rev 0) +++ trunk/gplots/R/lmplot2.R 2013-10-15 02:09:31 UTC (rev 1738) @@ -0,0 +1,183 @@ +plot.lm2 <- function( + x, + which = 1:5, + caption = c("Residuals vs Fitted", "Normal Q-Q plot", + "Scale-Location plot", "Cook's distance plot"), + panel = panel.smooth, + sub.caption = deparse(x$call), + main = "", + ask = interactive() && nb.fig < length(which) + && .Device != "postscript", + ..., + id.n = 3, + labels.id = names(residuals(x)), + cex.id = 0.75, + band=TRUE, + rug=TRUE, + width=1/10, + max.n=5000 + ) +{ + cl <- match.call() + mf <- match.call(expand.dots = FALSE) + mf[[1L]] <- quote(lmplot2) + eval(mf, parent.frame()) +} + + +lmplot2 <- function( + x, + which = 1:5, + caption = c("Residuals vs Fitted", "Normal Q-Q plot", + "Scale-Location plot", "Cook's distance plot"), + panel = panel.smooth, + sub.caption = deparse(x$call), + main = "", + ask = interactive() && nb.fig < length(which) + && .Device != "postscript", + ..., + id.n = 3, + labels.id = names(residuals(x)), + cex.id = 0.75, + band=TRUE, + rug=TRUE, + width=1/10, + max.n=5000 + ) +{ + if (!inherits(x, "lm")) + stop("Use only with 'lm' objects") + show <- rep(FALSE, 5) + if(!is.numeric(which) || any(which < 1) || any(which > 5)) + stop("`which' must be in 1:5") + show[which] <- TRUE + r <- residuals(x) + n <- length(r) + if(inherits(x,"glm")) + yh <- predict(x) # != fitted() for glm + else + yh <- fitted(x) + if (any(show[2:4])) + s <- if(inherits(x, "rlm")) x$s else sqrt(deviance(x)/df.residual(x)) + if (any(show[2:3])) { + ylab23 <- if(inherits(x, "glm")) + "Std. deviance resid." else "Standardized residuals" + hii <- lm.influence(x)$hat + w <- weights(x) + # r.w := weighted.residuals(x): + r.w <- if(is.null(w)) r else (sqrt(w)*r)[w!=0] + rs <- r.w/(s * sqrt(1 - hii)) + } + if (any(show[c(1,3)])) + l.fit <- if(inherits(x,"glm")) + "Predicted values" else "Fitted values" + if (is.null(id.n)) + id.n <- 0 + else { + id.n <- as.integer(id.n) + if(id.n < 0 || id.n > n) + stop(paste("`id.n' must be in { 1,..,",n,"}")) + } + if(id.n > 0) { + if(is.null(labels.id)) + labels.id <- paste(1:n) + iid <- 1:id.n + show.r <- order(-abs(r))[iid] + if(any(show[2:3])) + show.rs <- order(-abs(rs))[iid] + text.id <- function(x,y, ind, adj.x = FALSE) + text(x - if(adj.x) strwidth(" ")*cex.id else 0, y, labels.id[ind], + cex = cex.id, xpd = TRUE, adj = if(adj.x) 1) + } + nb.fig <- prod(par("mfcol")) + one.fig <- prod(par("mfcol")) == 1 + if (ask) { + op <- par(ask = TRUE) + on.exit(par(op)) + } + ##---------- Do the individual plots : ---------- + if (show[1]) { + ylim <- range(r) + if(id.n > 0) + ylim <- ylim + c(-1,1)* 0.08 * diff(ylim) + plot(yh, r, xlab = l.fit, ylab = "Residuals", main = main, + ylim = ylim, type = "n", ...) + panel(yh, r, ...) + if(rug) rug(yh) ## GRW 2001-06-08 + if(band) bandplot(yh,r,add=TRUE,width=width) ## GRW 2001-06-08 + if (one.fig) + title(sub = sub.caption, ...) + mtext(caption[1], 3, 0.25) + if(id.n > 0) { + y.id <- r[show.r] + y.id[y.id < 0] <- y.id[y.id < 0] - strheight(" ")/3 + text.id(yh[show.r], y.id, show.r, adj.x = TRUE) + } + abline(h = 0, lty = 3, col = "gray") + } + if (show[2]) { + ylim <- range(rs) + ylim[2] <- ylim[2] + diff(ylim) * 0.075 + qq <- qqnorm(rs, main = main, ylab = ylab23, ylim = ylim, ...) + qqline(rs) + if (one.fig) + title(sub = sub.caption, ...) + mtext(caption[2], 3, 0.25) + if(id.n > 0) + text.id(qq$x[show.rs], qq$y[show.rs], show.rs, adj.x = TRUE) + } + if (show[3]) { + sqrtabsr <- sqrt(abs(rs)) + ylim <- c(0, max(sqrtabsr)) + yl <- as.expression(substitute(sqrt(abs(YL)), list(YL=as.name(ylab23)))) + yhn0 <- if(is.null(w)) yh else yh[w!=0] + plot(yhn0, sqrtabsr, xlab = l.fit, ylab = yl, main = main, + ylim = ylim, type = "n", ...) + panel(yhn0, sqrtabsr, ...) + + abline(h=mean(sqrtabsr),lty = 3, col = "gray") + if(rug) rug(yh) ## GRW 2001-06-08 + if(band) bandplot(yhn0,sqrtabsr,add=TRUE) ## GRW 2001-06-08 + + if (one.fig) + title(sub = sub.caption, ...) + mtext(caption[3], 3, 0.25) + if(id.n > 0) + text.id(yhn0[show.rs], sqrtabsr[show.rs], show.rs, adj.x = TRUE) + } + if (show[4]) { + cook <- cooks.distance(x, sd=s) + if(id.n > 0) { + show.r <- order(-cook)[iid]# index of largest `id.n' ones + ymx <- cook[show.r[1]] * 1.075 + } else ymx <- max(cook) + plot(cook, type = "h", ylim = c(0, ymx), main = main, + xlab = "Obs. number", ylab = "Cook's distance", ...) + if (one.fig) + title(sub = sub.caption, ...) + mtext(caption[4], 3, 0.25) + if(id.n > 0) + text.id(show.r, cook[show.r] + 0.4*cex.id * strheight(" "), show.r) + } + if (show[5]) + { + ## plot residuals against each predictor ## + data <- model.frame(x) + for( i in 2:ncol(data) ) + { + test <- try( + { + plot.default( x=data[,i], y=r, + xlab=names(data)[i], ylab="Residuals", type="n") + panel( data[,i], r, ... ) + if(rug) rug(data[,i]) + if(band) bandplot(data[,i],r,add=TRUE) + abline(h=0,lty = 3, col = "gray") + } + ) + } + } + if (!one.fig && par("oma")[3] >= 1) + mtext(sub.caption, outer = TRUE, cex = 1.25) + invisible() +} Deleted: trunk/gplots/R/plot.lm.R =================================================================== --- trunk/gplots/R/plot.lm.R 2013-10-15 01:47:31 UTC (rev 1737) +++ trunk/gplots/R/plot.lm.R 2013-10-15 02:09:31 UTC (rev 1738) @@ -1,156 +0,0 @@ -plot.lm2 <- function( - x, - which = 1:5, - caption = c("Residuals vs Fitted", "Normal Q-Q plot", - "Scale-Location plot", "Cook's distance plot"), - panel = panel.smooth, - sub.caption = deparse(x$call), - main = "", - ask = interactive() && nb.fig < length(which) - && .Device != "postscript", - ..., - id.n = 3, - labels.id = names(residuals(x)), - cex.id = 0.75, - band=TRUE, - rug=TRUE, - width=1/10, - max.n=5000 - ) -{ - if (!inherits(x, "lm")) - stop("Use only with 'lm' objects") - show <- rep(FALSE, 5) - if(!is.numeric(which) || any(which < 1) || any(which > 5)) - stop("`which' must be in 1:5") - show[which] <- TRUE - r <- residuals(x) - n <- length(r) - if(inherits(x,"glm")) - yh <- predict(x) # != fitted() for glm - else - yh <- fitted(x) - if (any(show[2:4])) - s <- if(inherits(x, "rlm")) x$s else sqrt(deviance(x)/df.residual(x)) - if (any(show[2:3])) { - ylab23 <- if(inherits(x, "glm")) - "Std. deviance resid." else "Standardized residuals" - hii <- lm.influence(x)$hat - w <- weights(x) - # r.w := weighted.residuals(x): - r.w <- if(is.null(w)) r else (sqrt(w)*r)[w!=0] - rs <- r.w/(s * sqrt(1 - hii)) - } - if (any(show[c(1,3)])) - l.fit <- if(inherits(x,"glm")) - "Predicted values" else "Fitted values" - if (is.null(id.n)) - id.n <- 0 - else { - id.n <- as.integer(id.n) - if(id.n < 0 || id.n > n) - stop(paste("`id.n' must be in { 1,..,",n,"}")) - } - if(id.n > 0) { - if(is.null(labels.id)) - labels.id <- paste(1:n) - iid <- 1:id.n - show.r <- order(-abs(r))[iid] - if(any(show[2:3])) - show.rs <- order(-abs(rs))[iid] - text.id <- function(x,y, ind, adj.x = FALSE) - text(x - if(adj.x) strwidth(" ")*cex.id else 0, y, labels.id[ind], - cex = cex.id, xpd = TRUE, adj = if(adj.x) 1) - } - nb.fig <- prod(par("mfcol")) - one.fig <- prod(par("mfcol")) == 1 - if (ask) { - op <- par(ask = TRUE) - on.exit(par(op)) - } - ##---------- Do the individual plots : ---------- - if (show[1]) { - ylim <- range(r) - if(id.n > 0) - ylim <- ylim + c(-1,1)* 0.08 * diff(ylim) - plot(yh, r, xlab = l.fit, ylab = "Residuals", main = main, - ylim = ylim, type = "n", ...) - panel(yh, r, ...) - if(rug) rug(yh) ## GRW 2001-06-08 - if(band) bandplot(yh,r,add=TRUE,width=width) ## GRW 2001-06-08 - if (one.fig) - title(sub = sub.caption, ...) - mtext(caption[1], 3, 0.25) - if(id.n > 0) { - y.id <- r[show.r] - y.id[y.id < 0] <- y.id[y.id < 0] - strheight(" ")/3 - text.id(yh[show.r], y.id, show.r, adj.x = TRUE) - } - abline(h = 0, lty = 3, col = "gray") - } - if (show[2]) { - ylim <- range(rs) - ylim[2] <- ylim[2] + diff(ylim) * 0.075 - qq <- qqnorm(rs, main = main, ylab = ylab23, ylim = ylim, ...) - qqline(rs) - if (one.fig) - title(sub = sub.caption, ...) - mtext(caption[2], 3, 0.25) - if(id.n > 0) - text.id(qq$x[show.rs], qq$y[show.rs], show.rs, adj.x = TRUE) - } - if (show[3]) { - sqrtabsr <- sqrt(abs(rs)) - ylim <- c(0, max(sqrtabsr)) - yl <- as.expression(substitute(sqrt(abs(YL)), list(YL=as.name(ylab23)))) - yhn0 <- if(is.null(w)) yh else yh[w!=0] - plot(yhn0, sqrtabsr, xlab = l.fit, ylab = yl, main = main, - ylim = ylim, type = "n", ...) - panel(yhn0, sqrtabsr, ...) - - abline(h=mean(sqrtabsr),lty = 3, col = "gray") - if(rug) rug(yh) ## GRW 2001-06-08 - if(band) bandplot(yhn0,sqrtabsr,add=TRUE) ## GRW 2001-06-08 - - if (one.fig) - title(sub = sub.caption, ...) - mtext(caption[3], 3, 0.25) - if(id.n > 0) - text.id(yhn0[show.rs], sqrtabsr[show.rs], show.rs, adj.x = TRUE) - } - if (show[4]) { - cook <- cooks.distance(x, sd=s) - if(id.n > 0) { - show.r <- order(-cook)[iid]# index of largest `id.n' ones - ymx <- cook[show.r[1]] * 1.075 - } else ymx <- max(cook) - plot(cook, type = "h", ylim = c(0, ymx), main = main, - xlab = "Obs. number", ylab = "Cook's distance", ...) - if (one.fig) - title(sub = sub.caption, ...) - mtext(caption[4], 3, 0.25) - if(id.n > 0) - text.id(show.r, cook[show.r] + 0.4*cex.id * strheight(" "), show.r) - } - if (show[5]) - { - ## plot residuals against each predictor ## - data <- model.frame(x) - for( i in 2:ncol(data) ) - { - test <- try( - { - plot.default( x=data[,i], y=r, - xlab=names(data)[i], ylab="Residuals", type="n") - panel( data[,i], r, ... ) - if(rug) rug(data[,i]) - if(band) bandplot(data[,i],r,add=TRUE) - abline(h=0,lty = 3, col = "gray") - } - ) - } - } - if (!one.fig && par("oma")[3] >= 1) - mtext(sub.caption, outer = TRUE, cex = 1.25) - invisible() -} Deleted: trunk/gplots/man/boxplot.n.Rd =================================================================== --- trunk/gplots/man/boxplot.n.Rd 2013-10-15 01:47:31 UTC (rev 1737) +++ trunk/gplots/man/boxplot.n.Rd 2013-10-15 02:09:31 UTC (rev 1738) @@ -1,57 +0,0 @@ -% $Id$ -% -% $Log$ -% Revision 1.5 2005/12/01 16:46:52 nj7w -% Updated Greg's email address -% -% Revision 1.4 2005/06/09 14:20:28 nj7w -% Updating the version number, and various help files to synchronize splitting of gregmisc bundle in 4 individual components. -% -% Revision 1.1.1.1 2005/05/25 22:15:30 nj7w -% Initial submission as an individual package -% -% Revision 1.3 2002/04/09 00:51:31 warneg -% -% Checkin for version 0.5.3 -% -% Revision 1.2 2001/08/25 05:46:21 warneg -% Added CVS header. -% -% Revision 1.1 2001/08/25 05:45:10 warneg -% Initial Checkin -% -\name{boxplot.n} -\alias{boxplot.n} -\title{Produce a Boxplot Annotated with the Number of Observations} -\description{ - This funcntion uses \code{boxplot} to produce a boxplot which is then - annotated with the number of observations in each group. -} -\usage{ -boxplot.n(..., top=FALSE, shrink=1, textcolor=NULL) -} -\arguments{ - \item{\dots}{ parameters passed to \code{boxplot}. } - \item{top}{ logical indicating whether the number of observations - should be added to the top or the bottom of the plotting - region. Defaults to \code{FALSE}. } - \item{shrink}{ value to shrink character size (cex) when annotating.} - \item{textcolor}{ text color. } -} -\author{ Gregory R. Warnes \email{gr...@wa...}} -\seealso{ \code{\link{boxplot}}, \code{\link{text}}} - -\examples{ -data(state) - -# n's at bottom -boxplot.n( state.area ~ state.region) - -# n's at top -boxplot.n( state.area ~ state.region, top=TRUE) - -# small red text -boxplot.n( state.area ~ state.region, shrink=0.8, textcolor="red") -} - -\keyword{ hplot } Deleted: trunk/gplots/man/boxplot2.Rd =================================================================== --- trunk/gplots/man/boxplot2.Rd 2013-10-15 01:47:31 UTC (rev 1737) +++ trunk/gplots/man/boxplot2.Rd 2013-10-15 02:09:31 UTC (rev 1738) @@ -1,57 +0,0 @@ -% $Id$ -% -% $Log$ -% Revision 1.5 2005/12/01 16:46:52 nj7w -% Updated Greg's email address -% -% Revision 1.4 2005/06/09 14:20:28 nj7w -% Updating the version number, and various help files to synchronize splitting of gregmisc bundle in 4 individual components. -% -% Revision 1.1.1.1 2005/05/25 22:15:30 nj7w -% Initial submission as an individual package -% -% Revision 1.3 2002/04/09 00:51:31 warneg -% -% Checkin for version 0.5.3 -% -% Revision 1.2 2001/08/25 05:46:21 warneg -% Added CVS header. -% -% Revision 1.1 2001/08/25 05:45:10 warneg -% Initial Checkin -% -\name{boxplot.n} -\alias{boxplot.n} -\title{Produce a Boxplot Annotated with the Number of Observations} -\description{ - This funcntion uses \code{boxplot} to produce a boxplot which is then - annotated with the number of observations in each group. -} -\usage{ -boxplot.n(..., top=FALSE, shrink=1, textcolor=NULL) -} -\arguments{ - \item{\dots}{ parameters passed to \code{boxplot}. } - \item{top}{ logical indicating whether the number of observations - should be added to the top or the bottom of the plotting - region. Defaults to \code{FALSE}. } - \item{shrink}{ value to shrink character size (cex) when annotating.} - \item{textcolor}{ text color. } -} -\author{ Gregory R. Warnes \email{gr...@wa...}} -\seealso{ \code{\link{boxplot}}, \code{\link{text}}} - -\examples{ -data(state) - -# n's at bottom -boxplot.n( state.area ~ state.region) - -# n's at top -boxplot.n( state.area ~ state.region, top=TRUE) - -# small red text -boxplot.n( state.area ~ state.region, shrink=0.8, textcolor="red") -} - -\keyword{ hplot } Copied: trunk/gplots/man/boxplot2.Rd (from rev 1672, trunk/gplots/man/boxplot.n.Rd) =================================================================== --- trunk/gplots/man/boxplot2.Rd (rev 0) +++ trunk/gplots/man/boxplot2.Rd 2013-10-15 02:09:31 UTC (rev 1738) @@ -0,0 +1,42 @@ +\name{boxplot2} +\alias{boxplot2} +\title{Produce a Boxplot Annotated with the Number of Observations} +\description{ + This funcntion uses \code{boxplot} to produce a boxplot which is then + annotated with the number of observations in each group. +} +\usage{ +boxplot2(..., top=FALSE, shrink=1, textcolor=NULL) +} +\arguments{ + \item{\dots}{ parameters passed to \code{boxplot}. } + \item{top}{ logical indicating whether the number of observations + should be added to the top or the bottom of the plotting + region. Defaults to \code{FALSE}. } + \item{shrink}{ value to shrink character size (cex) when annotating.} + \item{textcolor}{ text color. } +} +\author{ Gregory R. Warnes \email{gr...@wa...}} +\note{ + This function replaces \code{boxplot.n}, which has been deprecated + avoid potential problems with S3 method dispatching. +} +\seealso{ + \code{\link{boxplot}}, + \code{\link{text}} +} + +\examples{ +data(state) + +# n's at bottom +boxplot2( state.area ~ state.region) + +# n's at top +boxplot2( state.area ~ state.region, top=TRUE) + +# small red text +boxplot2( state.area ~ state.region, shrink=0.8, textcolor="red") +} + +\keyword{ hplot } Modified: trunk/gplots/man/gplots-deprecated.Rd =================================================================== --- trunk/gplots/man/gplots-deprecated.Rd 2013-10-15 01:47:31 UTC (rev 1737) +++ trunk/gplots/man/gplots-deprecated.Rd 2013-10-15 02:09:31 UTC (rev 1738) @@ -1,57 +1,53 @@ -% $Id$ -% -% $Log$ -% Revision 1.5 2005/12/01 16:46:52 nj7w -% Updated Greg's email address -% -% Revision 1.4 2005/06/09 14:20:28 nj7w -% Updating the version number, and various help files to synchronize splitting of gregmisc bundle in 4 individual components. -% -% Revision 1.1.1.1 2005/05/25 22:15:30 nj7w -% Initial submission as an individual package -% -% Revision 1.3 2002/04/09 00:51:31 warneg -% -% Checkin for version 0.5.3 -% -% Revision 1.2 2001/08/25 05:46:21 warneg -% Added CVS header. -% -% Revision 1.1 2001/08/25 05:45:10 warneg -% Initial Checkin -% -\name{boxplot.n} +\name{gplots-deprecated} \alias{boxplot.n} -\title{Produce a Boxplot Annotated with the Number of Observations} +\alias{plot.lm2} +\title{Deprecated functions} \description{ - This funcntion uses \code{boxplot} to produce a boxplot which is then - annotated with the number of observations in each group. + These funcntion have been deprecated and will be removed in future + releases of gplots. } \usage{ -boxplot.n(..., top=FALSE, shrink=1, textcolor=NULL) + boxplot.n(..., top=FALSE, shrink=1, textcolor=NULL) + plot.lm2( + x, + which = 1:5, + caption = c("Residuals vs Fitted", "Normal Q-Q plot", + "Scale-Location plot", "Cook's distance plot"), + panel = panel.smooth, + sub.caption = deparse(x$call), + main = "", + ask = interactive() && nb.fig < length(which) + && .Device != "postscript", + ..., + id.n = 3, + labels.id = names(residuals(x)), + cex.id = 0.75, + band=TRUE, + rug=TRUE, + width=1/10, + max.n=5000 + ) } \arguments{ - \item{\dots}{ parameters passed to \code{boxplot}. } - \item{top}{ logical indicating whether the number of observations - should be added to the top or the bottom of the plotting - region. Defaults to \code{FALSE}. } - \item{shrink}{ value to shrink character size (cex) when annotating.} - \item{textcolor}{ text color. } + \item{\dots}{see man page for the corresponding replacement function} + \item{top, shrink, textcolor}{See man page for + \code{\link{boxplot2}}.} + \item{x, which, caption, panel, sub.caption, main, ask, id.n, + labels.id, cex.id, band, rug, width, max.n}{See man page for + \code{\link{lmplot2}}.} } -\author{ Gregory R. Warnes \email{gr...@wa...}} -\seealso{ \code{\link{boxplot}}, \code{\link{text}}} - -\examples{ -data(state) - -# n's at bottom -boxplot.n( state.area ~ state.region) - -# n's at top -boxplot.n( state.area ~ state.region, top=TRUE) - -# small red text -boxplot.n( state.area ~ state.region, shrink=0.8, textcolor="red") +\details{ +These functions have been deprecated. Please refer to the manual page +for the replacement function: + \itemize{ + \item \code{boxplot.n} has been replaced by \code{\link{boxplot2}} + \item \code{plot.lm2} has been replaced by \code{\link{lmplot2}} + } } - -\keyword{ hplot } +\author{Gregory R. Warnes \email{gr...@wa...}} +\seealso{ + \code{\link{boxplot2}}, + \code{\link{lmplot2}}, + \code{\link[base]{Deprecated}} +} +\keyword{misc} Deleted: trunk/gplots/man/lmplot2.Rd =================================================================== --- trunk/gplots/man/lmplot2.Rd 2013-10-15 01:47:31 UTC (rev 1737) +++ trunk/gplots/man/lmplot2.Rd 2013-10-15 02:09:31 UTC (rev 1738) @@ -1,71 +0,0 @@ -\name{plot.lm2} -\alias{plot.lm2} -\title{ - Plots to assess the goodness of fit for the linear model objects -} -\description{ - Plots to assess the goodness of fit for the linear model objects - } - \usage{ - plot.lm2( - x, - which = 1:5, - caption = c("Residuals vs Fitted", "Normal Q-Q plot", - "Scale-Location plot", "Cook's distance plot"), - panel = panel.smooth, - sub.caption = deparse(x$call), - main = "", - ask = interactive() && nb.fig < length(which) - && .Device != "postscript", - ..., - id.n = 3, - labels.id = names(residuals(x)), - cex.id = 0.75, - band=TRUE, - rug=TRUE, - width=1/10, - max.n=5000 - ) -} -\arguments{ - \item{x}{lm object} - \item{which}{Numerical values between 1 and 5, indicating which plots - to be shown. The codes are: - - 1- fitted vs residuals plot - 2- Normal Q-Q plot - 3- Scale-Location plot - 4- Cook's distance plot - 5- residuals vs each predictor plot - } - \item{caption}{ Caption for each type of plot} - \item{panel}{ function to draw on the existing plot} - \item{sub.caption}{ SubCaption for the plots } - \item{main}{Main title of the plot} - \item{ask}{whether interactive graphics or postscript } - \item{\dots}{ parameters passed to \code{plot.lm2}. } - \item{id.n}{ integer value, less than or equal to residuals of lm object } - \item{labels.id}{Names of the residuals of the lm object} - \item{cex.id}{Parameter to control the height of text stringsx} - \item{band}{logical vector indicating whether bandplot should also be plotted } - \item{rug}{logical vector indicating whether rug should be added to - the existing plot } - \item{width}{Fraction of the data to use for plot smooths} - \item{max.n}{Maximum number of points to display in plots} -} -\author{Gregory R. Warnes \email{gr...@wa...} and Nitin - Jain \email{nit...@pf...}} -\examples{ -ctl <- rnorm(100, 4) -trt <- rnorm(100, 4.5) -group <- gl(2,100,200, labels=c("Ctl","Trt")) -weight <- c(ctl, trt) -wt.err <- rnorm(length(weight), mean=weight, sd=1/2) -x <- lm(weight ~ group + wt.err) - -plot.lm2(x) - -plot.lm2(x, which=1, width=1/3) -plot.lm2(x, which=1:3, widht=1/3) -} -\keyword{hplot} Copied: trunk/gplots/man/lmplot2.Rd (from rev 1735, trunk/gplots/man/plot.lm2.Rd) =================================================================== --- trunk/gplots/man/lmplot2.Rd (rev 0) +++ trunk/gplots/man/lmplot2.Rd 2013-10-15 02:09:31 UTC (rev 1738) @@ -0,0 +1,79 @@ +\name{lmplot2} +\alias{lmplot2} +\title{ + Plots to assess the goodness of fit for the linear model objects +} +\description{ + Plots to assess the goodness of fit for the linear model objects + } + \usage{ + lmplot2( + x, + which = 1:5, + caption = c("Residuals vs Fitted", "Normal Q-Q plot", + "Scale-Location plot", "Cook's distance plot"), + panel = panel.smooth, + sub.caption = deparse(x$call), + main = "", + ask = interactive() && nb.fig < length(which) + && .Device != "postscript", + ..., + id.n = 3, + labels.id = names(residuals(x)), + cex.id = 0.75, + band=TRUE, + rug=TRUE, + width=1/10, + max.n=5000 + ) +} +\arguments{ + \item{x}{lm object} + \item{which}{Numerical values between 1 and 5, indicating which plots + to be shown. The codes are: + \describe{ + \item{1}{Fitted vs residuals} + \item{2}{Normal Q-Q} + \item{3}{Scale-Location} + \item{4}{Cook's distance} + \item{5}{Residuals vs. predictor} + } + } + \item{caption}{ Caption for each type of plot} + \item{panel}{ function to draw on the existing plot} + \item{sub.caption}{ SubCaption for the plots } + \item{main}{Main title of the plot} + \item{ask}{whether interactive graphics or postscript } + \item{\dots}{ parameters passed to \code{lmplot2}. } + \item{id.n}{ integer value, less than or equal to residuals of lm object } + \item{labels.id}{Names of the residuals of the lm object} + \item{cex.id}{Parameter to control the height of text stringsx} + \item{band}{logical vector indicating whether bandplot should also be plotted } + \item{rug}{logical vector indicating whether rug should be added to + the existing plot } + \item{width}{Fraction of the data to use for plot smooths} + \item{max.n}{Maximum number of points to display in plots} +} +\note{ + This function replaces \code{boxplot.n}, which has been deprecated + avoid potential problems with S3 method dispatching. +} +\author{Gregory R. Warnes \email{gr...@wa...} and Nitin + Jain \email{nit...@pf...}} +\seealso{ + \code{\link[stats]{plot.lm}} + } +\examples{ +ctl <- rnorm(100, 4) +trt <- rnorm(100, 4.5) +group <- gl(2,100,200, labels=c("Ctl","Trt")) +weight <- c(ctl, trt) +wt.err <- rnorm(length(weight), mean=weight, sd=1/2) +x <- lm(weight ~ group + wt.err) + +lmplot2(x) + +lmplot2(x, which=1, width=1/3) +lmplot2(x, which=1:3, widht=1/3) +} +\keyword{hplot} Deleted: trunk/gplots/man/plot.lm2.Rd =================================================================== --- trunk/gplots/man/plot.lm2.Rd 2013-10-15 01:47:31 UTC (rev 1737) +++ trunk/gplots/man/plot.lm2.Rd 2013-10-15 02:09:31 UTC (rev 1738) @@ -1,71 +0,0 @@ -\name{plot.lm2} -\alias{plot.lm2} -\title{ - Plots to assess the goodness of fit for the linear model objects -} -\description{ - Plots to assess the goodness of fit for the linear model objects - } - \usage{ - plot.lm2( - x, - which = 1:5, - caption = c("Residuals vs Fitted", "Normal Q-Q plot", - "Scale-Location plot", "Cook's distance plot"), - panel = panel.smooth, - sub.caption = deparse(x$call), - main = "", - ask = interactive() && nb.fig < length(which) - && .Device != "postscript", - ..., - id.n = 3, - labels.id = names(residuals(x)), - cex.id = 0.75, - band=TRUE, - rug=TRUE, - width=1/10, - max.n=5000 - ) -} -\arguments{ - \item{x}{lm object} - \item{which}{Numerical values between 1 and 5, indicating which plots - to be shown. The codes are: - - 1- fitted vs residuals plot - 2- Normal Q-Q plot - 3- Scale-Location plot - 4- Cook's distance plot - 5- residuals vs each predictor plot - } - \item{caption}{ Caption for each type of plot} - \item{panel}{ function to draw on the existing plot} - \item{sub.caption}{ SubCaption for the plots } - \item{main}{Main title of the plot} - \item{ask}{whether interactive graphics or postscript } - \item{\dots}{ parameters passed to \code{plot.lm2}. } - \item{id.n}{ integer value, less than or equal to residuals of lm object } - \item{labels.id}{Names of the residuals of the lm object} - \item{cex.id}{Parameter to control the height of text stringsx} - \item{band}{logical vector indicating whether bandplot should also be plotted } - \item{rug}{logical vector indicating whether rug should be added to - the existing plot } - \item{width}{Fraction of the data to use for plot smooths} - \item{max.n}{Maximum number of points to display in plots} -} -\author{Gregory R. Warnes \email{gr...@wa...} and Nitin - Jain \email{nit...@pf...}} -\examples{ -ctl <- rnorm(100, 4) -trt <- rnorm(100, 4.5) -group <- gl(2,100,200, labels=c("Ctl","Trt")) -weight <- c(ctl, trt) -wt.err <- rnorm(length(weight), mean=weight, sd=1/2) -x <- lm(weight ~ group + wt.err) - -plot.lm2(x) - -plot.lm2(x, which=1, width=1/3) -plot.lm2(x, which=1:3, widht=1/3) -} -\keyword{hplot} This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2013-10-15 02:13:16
|
Revision: 1739 http://sourceforge.net/p/r-gregmisc/code/1739 Author: warnes Date: 2013-10-15 02:13:13 +0000 (Tue, 15 Oct 2013) Log Message: ----------- Update for gplots release 2.12.1 Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2013-10-15 02:09:31 UTC (rev 1738) +++ trunk/gplots/DESCRIPTION 2013-10-15 02:13:13 UTC (rev 1739) @@ -4,8 +4,8 @@ Depends: R (>= 3.0) Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS -Version: 2.12.0 -Date: 2013-10-11 +Version: 2.12.1 +Date: 2013-10-14 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2013-10-15 02:09:31 UTC (rev 1738) +++ trunk/gplots/inst/NEWS 2013-10-15 02:13:13 UTC (rev 1739) @@ -1,6 +1,14 @@ -Release 2.12.0 - 2013-10-11 +Release 2.12.0 - 2013-10-14 --------------------------- +API Changes: + +- boxplot.n() has been renamed to boxplot2() to avoid potential S3 + method calling issues. + +- plot.lm2() has been rename to lmplot2() to avoid potential S3 method + calling issues. + Enhancements: - Add heatmap.2() parameters to control row and column label rotation This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-04-04 22:37:16
|
Revision: 1779 http://sourceforge.net/p/r-gregmisc/code/1779 Author: warnes Date: 2014-04-04 22:37:12 +0000 (Fri, 04 Apr 2014) Log Message: ----------- Update for gplots 2.13.0 Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2014-04-04 21:32:51 UTC (rev 1778) +++ trunk/gplots/DESCRIPTION 2014-04-04 22:37:12 UTC (rev 1779) @@ -4,12 +4,12 @@ Depends: R (>= 3.0) Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS -Version: 2.12.1 -Date: 2013-10-14 +Version: 2.13.0 +Date: 2014-04-04 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill - Venables + Venables Maintainer: Gregory R. Warnes <gr...@wa...> License: GPL-2 NeedsCompilation: No Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2014-04-04 21:32:51 UTC (rev 1778) +++ trunk/gplots/inst/NEWS 2014-04-04 22:37:12 UTC (rev 1779) @@ -1,3 +1,18 @@ +Release 2.13.0 - 2014-04-04 +--------------------------- + +Bug Fixes: + +- heatmap.2 was not properly handling row trace reference line ('hline'). + Patch submitted by Ilia Kats. + +Enhancements: + +- When the row or column trace is enabled, show the corresponding + reference line in the color key. + + + Release 2.12.1 - 2013-10-14 --------------------------- @@ -23,7 +38,7 @@ finite values. Other Changes: - + - Changes to overplot() to avoid warnings from upcoming enhancements to R CMD check. - Move several packages from Depends to Imports or Suggests. This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-04-05 00:10:18
|
Revision: 1780 http://sourceforge.net/p/r-gregmisc/code/1780 Author: warnes Date: 2014-04-05 00:10:13 +0000 (Sat, 05 Apr 2014) Log Message: ----------- Add 'extrafun' argument to heatmap.2 to allow the user to perform additional customization by providing a function to be called before heatmap.2 exits. Modified Paths: -------------- trunk/gplots/R/heatmap.2.R trunk/gplots/man/heatmap.2.Rd Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-04-04 22:37:12 UTC (rev 1779) +++ trunk/gplots/R/heatmap.2.R 2014-04-05 00:10:13 UTC (rev 1780) @@ -78,6 +78,7 @@ lwid = NULL, ## extras + extrafun=NULL, ... ) { @@ -641,9 +642,6 @@ } } - - - } else plot.new() @@ -655,6 +653,9 @@ color=retval$col ) + ## If user has provided an extra function, call it. + if(!is.null(extrafun)) + extrafun() invisible( retval ) } Modified: trunk/gplots/man/heatmap.2.Rd =================================================================== --- trunk/gplots/man/heatmap.2.Rd 2014-04-04 22:37:12 UTC (rev 1779) +++ trunk/gplots/man/heatmap.2.Rd 2014-04-05 00:10:13 UTC (rev 1780) @@ -3,7 +3,7 @@ \title{ Enhanced Heat Map } \description{ A heat map is a false color image (basically - \code{\link{image}(t(x))}) with a dendrogram added to the left side + \code{\link{image}(t(x))}) with a dendrogram added to the left side and/or to the top. Typically, reordering of the rows and columns according to some set of values (row or column means) within the restrictions imposed by the dendrogram is carried out. @@ -90,6 +90,7 @@ lwid = NULL, # extras + extrafun=NULL, ... ) } @@ -112,7 +113,7 @@ \item{hclustfun}{function used to compute the hierarchical clustering when \code{Rowv} or \code{Colv} are not dendrograms. Defaults to \code{\link{hclust}}.} - \item{dendrogram}{character string indicating whether to draw 'none', + \item{dendrogram}{character string indicating whether to draw 'none', 'row', 'column' or 'both' dendrograms. Defaults to 'both'. However, if Rowv (or Colv) is FALSE or NULL and dendrogram is 'both', then a warning is issued and Rowv (or Colv) arguments are honoured.} @@ -182,12 +183,12 @@ for the row or column axis labeling. The defaults currently only use number of rows or columns, respectively.} \item{labRow, labCol}{character vectors with row and column labels to - use; these default to \code{rownames(x)} or \code{colnames(x)}, + use; these default to \code{rownames(x)} or \code{colnames(x)}, respectively.} \item{srtRow, srtCol}{angle of row/column labels, in degrees from horizontal} \item{adjRow, adjCol}{2-element vector giving the (left-right, top-bottom) justification of row/column labels (relative to the text - orientation).} + orientation).} \item{offsetRow, offsetCol}{Number of character-width spaces to place between row/column labels and the edge of the plotting region.} % Color key and density info @@ -211,7 +212,9 @@ % figure layout \item{lmat, lhei, lwid}{visual layout: position matrix, column height, column width. See below for details} - \item{...}{additional arguments passed on to \code{\link{image}} } % + \item{extrafun}{A function to be called after all other work. See + examples.} + \item{...}{additional arguments passed on to \code{\link{image}} } } \details{ If either \code{Rowv} or \code{Colv} are dendrograms they are honored @@ -221,11 +224,11 @@ If either is a vector (of \dQuote{weights}) then the appropriate dendrogram is reordered according to the supplied values subject to - the constraints imposed by the dendrogram, by \code{\link{reorder}(dd, + the constraints imposed by the dendrogram, by \code{\link{reorder}(dd, Rowv)}, in the row case. %% If either is missing, as by default, then the ordering of the - corresponding dendrogram is by the mean value of the rows/columns, + corresponding dendrogram is by the mean value of the rows/columns, i.e., in the case of rows, \code{Rowv <- rowMeans(x, na.rm=na.rm)}. %% If either is \code{\link{NULL}}, \emph{no reordering} will be done for @@ -237,7 +240,7 @@ The default colors range from red to white (\code{heat.colors}) and are not pretty. Consider using enhancements such - as the \pkg{RColorBrewer} package, + as the \pkg{RColorBrewer} package, \url{http://cran.r-project.org/src/contrib/PACKAGES.html#RColorBrewer} to select better colors. @@ -286,9 +289,9 @@ \item{hline}{center-line value used for row trace, present only if \code{trace="both"} or \code{trace="row"} } \item{colorTable}{A three-column data frame providing the lower and upper - bound and color for each bin} + bound and color for each bin} } -\author{Andy Liaw, original; R. Gentleman, M. Maechler, W. Huber, +\author{Andy Liaw, original; R. Gentleman, M. Maechler, W. Huber, G. Warnes, revisions.} \seealso{\code{\link{image}}, \code{\link{hclust}}} @@ -303,7 +306,7 @@ ## ## demonstrate the effect of row and column dendogram options ## - heatmap.2(x) ## default - dendrogram plotted and reordering done. + heatmap.2(x) ## default - dendrogram plotted and reordering done. heatmap.2(x, dendrogram="none") ## no dendrogram plotted, but reordering done. heatmap.2(x, dendrogram="row") ## row dendrogram plotted and row reordering done. heatmap.2(x, dendrogram="col") ## col dendrogram plotted and col reordering done. @@ -341,7 +344,21 @@ heatmap.2(x, srtRow=0, srtCol=90, offsetRow=2, offsetCol=2) heatmap.2(x, srtRow=0, srtCol=90, offsetRow=-1, offsetCol=-1) - ## + ## Show how to use 'extrafun' to replace the 'key' with a scatterplot + lmat <- rbind( c(5,3,4), c(2,1,4) ) + lhei <- c(1.5, 4) + lwid <- c(1.5, 4, 0.75) + + myplot <- function() { + oldpar <- par("mar") + par(mar=c(5.1, 4.1, 0.5, 0.5)) + plot(mpg ~ hp, data=x) + } + + heatmap.2(x, lmat=lmat, lhei=lhei, lwid=lwid, key=FALSE, extrafun=myplot) + + + ## ## Show effect of z-score scaling within columns, blue-red color scale ## hv <- heatmap.2(x, col=bluered, scale="column", tracecol="#303030") @@ -364,18 +381,18 @@ ## ## A more decorative heatmap, with z-score scaling along columns ## - hv <- heatmap.2(x, col=cm.colors(255), scale="column", - RowSideColors=rc, ColSideColors=cc, margin=c(5, 10), - xlab="specification variables", ylab= "Car Models", - main="heatmap(<Mtcars data>, ..., scale=\"column\")", + hv <- heatmap.2(x, col=cm.colors(255), scale="column", + RowSideColors=rc, ColSideColors=cc, margin=c(5, 10), + xlab="specification variables", ylab= "Car Models", + main="heatmap(<Mtcars data>, ..., scale=\"column\")", tracecol="green", density="density") ## Note that the breakpoints are now symmetric about 0 - + %% want example using the `add.exp' argument! data(attitude) @@ -398,7 +415,7 @@ data(USJudgeRatings) symnum( cU <- cor(USJudgeRatings) ) - hU <- heatmap.2(cU, Rowv=FALSE, symm=TRUE, col=topo.colors(16), + hU <- heatmap.2(cU, Rowv=FALSE, symm=TRUE, col=topo.colors(16), distfun=function(c) as.dist(1 - c), trace="none") ## The Correlation matrix with same reordering: @@ -407,8 +424,8 @@ # now with the correlation matrix on the plot itself - heatmap.2(cU, Rowv=FALSE, symm=TRUE, col=rev(heat.colors(16)), - distfun=function(c) as.dist(1 - c), trace="none", + heatmap.2(cU, Rowv=FALSE, symm=TRUE, col=rev(heat.colors(16)), + distfun=function(c) as.dist(1 - c), trace="none", cellnote=hM) ## genechip data examples @@ -418,15 +435,15 @@ pms <- SpikeIn@pm # just the data, scaled across rows - heatmap.2(pms, col=rev(heat.colors(16)), main="SpikeIn@pm", - xlab="Relative Concentration", ylab="Probeset", + heatmap.2(pms, col=rev(heat.colors(16)), main="SpikeIn@pm", + xlab="Relative Concentration", ylab="Probeset", scale="row") # fold change vs "12.50" sample data <- pms / pms[, "12.50"] data <- ifelse(data>1, data, -1/data) - heatmap.2(data, breaks=16, col=redgreen, tracecol="blue", - main="SpikeIn@pm Fold Changes\nrelative to 12.50 sample", + heatmap.2(data, breaks=16, col=redgreen, tracecol="blue", + main="SpikeIn@pm Fold Changes\nrelative to 12.50 sample", xlab="Relative Concentration", ylab="Probeset") } 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:36:29
|
Revision: 1821 http://sourceforge.net/p/r-gregmisc/code/1821 Author: warnes Date: 2014-06-19 18:36:19 +0000 (Thu, 19 Jun 2014) Log Message: ----------- Update for gplots 2.14.0 Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2014-06-17 23:22:57 UTC (rev 1820) +++ trunk/gplots/DESCRIPTION 2014-06-19 18:36:19 UTC (rev 1821) @@ -4,8 +4,8 @@ Depends: R (>= 3.0) Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS -Version: 2.13.0 -Date: 2014-04-04 +Version: 2.14.0 +Date: 2014-06-19 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2014-06-17 23:22:57 UTC (rev 1820) +++ trunk/gplots/inst/NEWS 2014-06-19 18:36:19 UTC (rev 1821) @@ -1,3 +1,27 @@ +Release 2.14.0 - 2014-06-18 +--------------------------- + +Bug Fixes: + +- heatmap.2(): Fix typo in heatmap.2() that caused an error when + 'Rowv=FALSE'. (Reported by Yuanhua Liu.) + +Enhancements: + +- heatmap.2(): Add new 'reorderfun' argument to allow the user to + specify an alternative function to reorder rows/columns based on + row/column dendrogram. (Suggested by Yuanhua Liu.) + +- heatmap.2(): Center margin labels. + +- heatmap.2(): Check size of user-provided Rowv and Colv dendrogram + objects to ensure they match the dimensions of the data. + +- Add references to man page for hist2d() and ci2d() to the new r2d2 + package which implements an improved algorithm for 2-dimensional + emprical confidence regions. + + Release 2.13.0 - 2014-04-04 --------------------------- This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-09-16 18:08:50
|
Revision: 1887 http://sourceforge.net/p/r-gregmisc/code/1887 Author: warnes Date: 2014-09-16 18:08:39 +0000 (Tue, 16 Sep 2014) Log Message: ----------- - Correct statement of default color for 'notecol' argumemt to 'heatmap.2'. - Modify default arguments to 'symbreaks' and 'symkey' to make the logic more evident by replacing min() with any(). (The previous code executed properly, but relied on implicit coercion of logicals to numeric, obscuring the intent.) Modified Paths: -------------- trunk/gplots/R/heatmap.2.R trunk/gplots/man/heatmap.2.Rd Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2014-09-13 01:17:27 UTC (rev 1886) +++ trunk/gplots/R/heatmap.2.R 2014-09-16 18:08:39 UTC (rev 1887) @@ -21,7 +21,7 @@ ## mapping data to colors breaks, - symbreaks=min(x < 0, na.rm=TRUE) || scale!="none", + symbreaks=any(x < 0, na.rm=TRUE) || scale!="none", ## colors col="heat.colors", @@ -65,7 +65,7 @@ keysize = 1.5, density.info=c("histogram","density","none"), denscol=tracecol, - symkey = min(x < 0, na.rm=TRUE) || symbreaks, + symkey = any(x < 0, na.rm=TRUE) || symbreaks, densadj = 0.25, key.title = NULL, key.xlab = NULL, @@ -555,7 +555,7 @@ if( dendrogram %in% c("both","column") ) { - plot(ddc, axes = FALSE, xaxs = "i", leaflab = "none") + plot.dendrogram(ddc, axes = FALSE, xaxs = "i", leaflab = "none") } else plot.new() Modified: trunk/gplots/man/heatmap.2.Rd =================================================================== --- trunk/gplots/man/heatmap.2.Rd 2014-09-13 01:17:27 UTC (rev 1886) +++ trunk/gplots/man/heatmap.2.Rd 2014-09-16 18:08:39 UTC (rev 1887) @@ -33,7 +33,7 @@ # mapping data to colors breaks, - symbreaks=min(x < 0, na.rm=TRUE) || scale!="none", + symbreaks=any(x < 0, na.rm=TRUE) || scale!="none", # colors col="heat.colors", @@ -77,7 +77,7 @@ keysize = 1.5, density.info=c("histogram","density","none"), denscol=tracecol, - symkey = min(x < 0, na.rm=TRUE) || symbreaks, + symkey = any(x < 0, na.rm=TRUE) || symbreaks, densadj = 0.25, key.title = NULL, key.xlab = NULL, @@ -126,7 +126,7 @@ warning is issued and Rowv (or Colv) arguments are honoured.} \item{reorderfun}{\code{function(d, w)} of dendrogram and weights for reordering the row and column dendrograms. The default uses - \code{\link{stats}{reorder.dendrogram}}. + \code{\link{stats}{reorder.dendrogram}} }. \item{symm}{logical indicating if \code{x} should be treated \bold{symm}etrically; can only be true when \code{x} is a square matrix.} % data scaling @@ -162,7 +162,7 @@ \item{notecex}{(optional) numeric scaling factor for \code{cellnote} items.} \item{notecol}{(optional) character string specifying the color for - \code{cellnote} text. Defaults to "green".} + \code{cellnote} text. Defaults to "cyan".} \item{na.color}{Color to use for missing value (\code{NA}). Defaults to the plot background color.} % level trace This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-09-17 22:08:22
|
Revision: 1893 http://sourceforge.net/p/r-gregmisc/code/1893 Author: warnes Date: 2014-09-17 22:08:20 +0000 (Wed, 17 Sep 2014) Log Message: ----------- Update DESCRIPTION and NEWS for gplots 2.14.2 Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2014-09-17 22:03:10 UTC (rev 1892) +++ trunk/gplots/DESCRIPTION 2014-09-17 22:08:20 UTC (rev 1893) @@ -4,8 +4,8 @@ Depends: R (>= 3.0) Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS -Version: 2.14.0 -Date: 2014-06-19 +Version: 2.14.1 +Date: 2014-06-30 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2014-09-17 22:03:10 UTC (rev 1892) +++ trunk/gplots/inst/NEWS 2014-09-17 22:08:20 UTC (rev 1893) @@ -1,3 +1,32 @@ +Release 2.14.2 - 2014-09-17 +--------------------------- + +Bug Fixes: + +- heatmap.2() was not respecting key.title=NA when density.info="none". + +- Correct the man page for heatmap.2 to state that the default color + for 'notecol' is cyan. + +- In heatmap.2(), modify default arguments to 'symbreaks' and 'symkey' + to make the logic more evident by replacing min(...) with + any(...). (The previous code executed properly, but relied on + implicit coercion of logicals to numeric, obscuring the intent.) + +- Calling heatmap.2 with deeply nested dendrograms could trigger a + 'node stack overflow' error. Now, this situation is deteceted, and + a message is generated indicating how to increase the relevant + recursion limit via options("expressions"=...). + +Release 2.14.1 - 2014-06-30 +--------------------------- + +Bug Fixes: + +- Correct heatmap.2() bug in Colv dendrogram object dimension checking introduced + in 2.14.0. (Reported by Yong Fuga Li.) + + Release 2.14.0 - 2014-06-18 --------------------------- This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2014-12-01 22:52:57
|
Revision: 1899 http://sourceforge.net/p/r-gregmisc/code/1899 Author: warnes Date: 2014-12-01 22:52:47 +0000 (Mon, 01 Dec 2014) Log Message: ----------- Convert bandplot to S3-method dispatch and add method for class formula. Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/R/bandplot.R trunk/gplots/man/bandplot.Rd Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2014-12-01 22:51:46 UTC (rev 1898) +++ trunk/gplots/DESCRIPTION 2014-12-01 22:52:47 UTC (rev 1899) @@ -4,8 +4,8 @@ Depends: R (>= 3.0) Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS -Version: 2.14.1 -Date: 2014-06-30 +Version: 2.15.0 +Date: 2014-12-01 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Modified: trunk/gplots/R/bandplot.R =================================================================== --- trunk/gplots/R/bandplot.R 2014-12-01 22:51:46 UTC (rev 1898) +++ trunk/gplots/R/bandplot.R 2014-12-01 22:52:47 UTC (rev 1899) @@ -1,6 +1,9 @@ # $Id$ -bandplot <- function(x,y, +bandplot <- function(x, ...) + UseMethod("bandplot") + +bandplot.default <- function(x, y, ..., add=FALSE, sd=c(-2:2), @@ -53,3 +56,70 @@ } } + + +bandplot.formula <- function(x, + data=parent.frame(), + subset, + na.action, + xlab=NULL, + ylab=NULL, + ..., + add=FALSE, + sd=c(-2:2), + sd.col=c("magenta","blue","red", + "blue","magenta"), + sd.lwd=c(2,2,3,2,2), + sd.lty=c(2,1,1,1,2), + method="frac", width=1/5, + n=50 + ) + { + if (missing(x) || (length(x) != 3)) + stop("x missing or incorrect") + if (missing(na.action)) + na.action <- getOption("na.action") + m <- match.call(expand.dots = FALSE) + if (is.matrix(eval(m$data, parent.frame()))) + m$data <- as.data.frame(data) + m$formula <- m$x + m$... <- m$x <- m$f <- m$iter <- m$delta <- NULL + m$xlab <- m$ylab <- m$add <- m$sd <- NULL + m$sd.col <- m$sd.lwd <- m$sd.lty <- NULL + m$method <- m$width <- m$n <- NULL + + m[[1]] <- as.name("model.frame") + mf <- eval(m, parent.frame()) + response <- attr(attr(mf, "terms"), "response") + + sx <- substitute(x) + + if (is.null(xlab)) { + if (mode(x) != "name") + xlab <- deparse(sx[[3L]]) + else + xlab <- "x" + } + + if (is.null(ylab)) { + if (mode(x) != "name") + ylab <- deparse(sx[[2L]]) + else + ylab <- "y" + } + + bandplot.default(x=mf[[-response]], + y=mf[[response]], + ..., + xlab=xlab, + ylab=ylab, + add=add, + sd=sd, + sd.col=sd.col, + sd.lwd=sd.lwd, + sd.lty=sd.lty, + method=method, + width=width, + n=n + ) + } Modified: trunk/gplots/man/bandplot.Rd =================================================================== --- trunk/gplots/man/bandplot.Rd 2014-12-01 22:51:46 UTC (rev 1898) +++ trunk/gplots/man/bandplot.Rd 2014-12-01 22:52:47 UTC (rev 1899) @@ -1,40 +1,32 @@ -% $Id$ -% -% $Log$ -% Revision 1.7 2005/12/01 16:46:52 nj7w -% Updated Greg's email address -% -% Revision 1.6 2005/06/09 14:20:28 nj7w -% Updating the version number, and various help files to synchronize splitting of gregmisc bundle in 4 individual components. -% -% Revision 1.1.1.1 2005/05/25 22:15:30 nj7w -% Initial submission as an individual package -% -% Revision 1.5 2003/11/19 14:52:32 warnes -% -% Remove extranious NULL that confused R CMD check. -% -% Revision 1.4 2002/09/23 13:59:30 warnes -% - Modified all files to include CVS Id and Log tags. -% -% - \name{bandplot} \alias{bandplot} +\alias{bandplot.formula} +\alias{bandplot.default} \title{Plot x-y Points with Locally Smoothed Mean and Standard Deviation} \description{ - Plot x-y Points with lines showing the locally smoothed mean and - standard deviation. - } + Plot x-y points with curves for locally smoothed mean and standard deviation. +} \usage{ - bandplot(x, y, ..., add = FALSE, sd = c(-2:2), +bandplot(x,...) +\method{bandplot}{formula}(x, data=parent.frame(), subset, na.action, ..., + xlab=NULL, ylab=NULL, add = FALSE, sd = c(-2:2), sd.col=c("magenta", "blue", "red", "blue", "magenta"), sd.lwd=c(2, 2, 3, 2, 2), sd.lty=c(2, 1, 1, 1, 2), - method = "frac", width = 1/5, n=50) + method = "frac", width = 1/5, n=50) +\method{bandplot}{default}(x, y, ..., add = FALSE, sd = c(-2:2), + sd.col=c("magenta", "blue", "red", "blue", "magenta"), + sd.lwd=c(2, 2, 3, 2, 2), sd.lty=c(2, 1, 1, 1, 2), + method = "frac", width = 1/5, n=50) } \arguments{ - \item{x}{numeric vector of x locations} - \item{y}{numeric vector of x locations} + \item{x}{either formula providing a single dependent variable (y) and + an single independent variable (x) to use as coordinates in the + scatter plot or a numeric vector of x locations} + \item{y}{numeric vector of y locations} + \item{data}{a data.frame (or list) from which the variables in `formula' + should be taken.} + \item{subset}{ an optional vector specifying a subset of observations to be + used in the fitting process. } \item{\dots}{Additional plotting parameters. } \item{add}{ Boolean indicating whether the local mean and standard deviation lines should be added to an existing plot. Defaults to This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-01-02 20:06:42
|
Revision: 1911 http://sourceforge.net/p/r-gregmisc/code/1911 Author: warnes Date: 2015-01-02 20:06:35 +0000 (Fri, 02 Jan 2015) Log Message: ----------- - plotmeans: Pass optional graphical arguments captured in '...' axis function used to draw the x axis. - plotmeans: Add an new argument 'text.n.label' to specify the text used for labelingthe number of elements in a group. Modified Paths: -------------- trunk/gplots/R/plotmeans.R trunk/gplots/man/plotmeans.Rd Modified: trunk/gplots/R/plotmeans.R =================================================================== --- trunk/gplots/R/plotmeans.R 2015-01-02 19:50:10 UTC (rev 1910) +++ trunk/gplots/R/plotmeans.R 2015-01-02 20:06:35 UTC (rev 1911) @@ -7,6 +7,7 @@ mean.labels=FALSE, ci.label=FALSE, n.label=TRUE, + text.n.label="N=", digits=getOption("digits"), col="black", barwidth=1, barcol="blue", @@ -78,7 +79,7 @@ xlab=xlab, ylab=ylab, labels=mean.labels, col=col, xlim=xlim, lwd=barwidth, barcol=barcol, minbar=minbar, maxbar=maxbar, ... ) if(invalid(xaxt) || xaxt!="n") - axis(1, at = 1:length(means), labels = legends) + axis(1, at = 1:length(means), labels = legends, ...) if(ci.label) { @@ -103,8 +104,12 @@ if(n.label) - text(x=1:length(means),y=par("usr")[3], - labels=paste("n=",ns,"\n",sep="")) + { + text(x=1:length(means), + y=par("usr")[3], + labels=paste(text.n.label, ns, "\n", sep="") + ) + } if(!invalid(connect) & !identical(connect,FALSE)) { @@ -120,6 +125,5 @@ lines(means, ..., lwd=lwd, col=ccol) } - } Modified: trunk/gplots/man/plotmeans.Rd =================================================================== --- trunk/gplots/man/plotmeans.Rd 2015-01-02 19:50:10 UTC (rev 1910) +++ trunk/gplots/man/plotmeans.Rd 2015-01-02 20:06:35 UTC (rev 1911) @@ -1,24 +1,17 @@ -% $Id$ - \name{plotmeans} \alias{plotmeans} \title{Plot Group Means and Confidence Intervals} \description{Plot group means and confidence intervals.} -%\synopsis{ \usage{ plotmeans(formula, data=NULL, subset, na.action, bars=TRUE, p=0.95, minsd=0, minbar, maxbar, xlab=names(mf)[2], ylab=names(mf)[1], mean.labels=FALSE, - ci.label=FALSE, n.label=TRUE, digits=getOption("digits"), - col="black", barwidth=1, barcol="blue", - connect=TRUE, ccol=col, legends=names(means), xaxt, - use.t=TRUE, lwd=par("lwd"), ...) + ci.label=FALSE, n.label=TRUE, text.n.label="n=", + digits=getOption("digits"), col="black", barwidth=1, + barcol="blue", connect=TRUE, ccol= + col, legends=names(means), xaxt, use.t=TRUE, + lwd=par("lwd"), ...) } -% -%\usage{ -% plotmeans( outcome ~ treatment) -%} - \arguments{ \item{formula}{symbolic expression specifying the outcome (continuous) and grouping variable (factor). See lm() for details.} @@ -42,12 +35,12 @@ \item{minbar}{minumum allowed value for bar ends. If specified, values smaller than \code{minbar} will be replaced with - \code{minbar}. } - + \code{minbar}. } + \item{maxbar}{maximum allowed value for bar ends. If specified, values larger than \code{maxbar} will be replaced with \code{maxbar}. } - + \item{xlab}{x-axis label.} \item{ylab}{y-axis label.} @@ -63,6 +56,9 @@ \item{n.label}{ a logical value indicating whether text giving the number of observations in each group should should be added to the plot. } + \item{text.n.label}{Prefix text for labeling observation counts. + Defaults to "n=". } + \item{digits}{ number of significant digits to use when displaying mean or confidince limit values.} @@ -86,22 +82,22 @@ \item{xaxt}{A character which specifies the axis type. Specifying `"n"' causes an axis to be set up, but not plotted.} - + \item{use.t}{ a logical value indicating whether the t distribution should be used to compute confidence intervals. If \code{TRUE}, the default, a t distribution will the correct number of degrees of freedom for each group be used. If \code{FALSE}, the a normal distribution will be used.} - + \item{lwd}{Width of connecting lines } - + \item{\dots}{ optional plotting parameters. } } -%\details{ -% -% +%\details{ +% +% %} @@ -109,7 +105,7 @@ # show comparison with boxplot data(state) - plotmeans(state.area ~ state.region) + plotmeans(state.area ~ state.region) # show some color and mean labels plotmeans(state.area ~ state.region, @@ -121,12 +117,12 @@ ccol="red", pch=7 ) # more complicated example showing how to show an interaction - data(esoph) + data(esoph) par(las=2, # use perpendicular axis labels mar=c(10.1,4.1,4.1,2.1), # create enough space for long x labels mgp=c(8,1,0) # move x axis legend down to avoid overlap ) - plotmeans(ncases/ncontrols ~ interaction(agegp , alcgp, sep =" "), + plotmeans(ncases/ncontrols ~ interaction(agegp , alcgp, sep =" "), connect=list(1:6,7:12,13:18,19:24), barwidth=2, col="dark green", @@ -137,7 +133,7 @@ "Ile-et-Vilaine Esophageal Cancer Study") ) abline(v=c(6.5, 12.5, 18.5), lty=2) - + } \author{Gregory R. Warnes \email{gr...@wa...}} This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-01-02 20:20:13
|
Revision: 1913 http://sourceforge.net/p/r-gregmisc/code/1913 Author: warnes Date: 2015-01-02 20:20:05 +0000 (Fri, 02 Jan 2015) Log Message: ----------- Update for gplots release 2.16.0. Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2015-01-02 20:10:21 UTC (rev 1912) +++ trunk/gplots/DESCRIPTION 2015-01-02 20:20:05 UTC (rev 1913) @@ -4,8 +4,8 @@ Depends: R (>= 3.0) Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS -Version: 2.15.0 -Date: 2014-12-01 +Version: 2.16.0 +Date: 2015-01-02 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2015-01-02 20:10:21 UTC (rev 1912) +++ trunk/gplots/inst/NEWS 2015-01-02 20:20:05 UTC (rev 1913) @@ -1,3 +1,17 @@ +Release 2.16.0 - 2015-01-02 +--------------------------- + +New Features: + +- plotmeans() has a new argument, 'text.n.label' which specifies the + text used for labeling the number of elements in a group. + +Bug Fixes: + +- plotmeans() now respects (optional) graphical arguments captured in + '...' when drawing the x axis. + + Release 2.15.0 - 2014-12-01 --------------------------- This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-04-22 21:33:14
|
Revision: 1930 http://sourceforge.net/p/r-gregmisc/code/1930 Author: warnes Date: 2015-04-22 21:33:06 +0000 (Wed, 22 Apr 2015) Log Message: ----------- heatmap.2: add new 'colRow' and 'colCol' arguments to control the color of row and column text labels Modified Paths: -------------- trunk/gplots/R/heatmap.2.R trunk/gplots/man/heatmap.2.Rd Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2015-04-14 22:02:42 UTC (rev 1929) +++ trunk/gplots/R/heatmap.2.R 2015-04-22 21:33:06 UTC (rev 1930) @@ -59,6 +59,8 @@ adjCol = c(NA,0), offsetRow = 0.5, offsetCol = 0.5, + colRow = NULL, + colCol = NULL, ## color key + density info key = TRUE, @@ -281,6 +283,12 @@ labCol <- if(is.null(colnames(x))) (1:nc)[colInd] else colnames(x) else labCol <- labCol[colInd] + + if(!is.null(colRow)) + colRow <- colRow[rowInd] + + if(!is.null(colCol)) + colCol <- colCol[colInd] if(scale == "row") { retval$rowMeans <- rm <- rowMeans(x, na.rm = na.rm) @@ -415,7 +423,7 @@ } ## add column labels - if(is.null(srtCol)) + if(is.null(srtCol) && is.null(colCol)) axis(1, 1:nc, labels= labCol, @@ -428,7 +436,7 @@ ) else { - if(is.numeric(srtCol)) + if(is.null(srtCol) || is.numeric(srtCol)) { if(missing(adjCol) || is.null(adjCol)) adjCol=c(1,NA) @@ -442,7 +450,10 @@ ##pos=1, adj=adjCol, cex=cexCol, - srt=srtCol) + srt=srtCol, + col=colCol + ) + print(colCol) par(xpd=xpd.orig) } else @@ -450,7 +461,7 @@ } ## add row labels - if(is.null(srtRow)) + if(is.null(srtRow) && is.null(colRow)) { axis(4, iy, @@ -465,7 +476,7 @@ } else { - if(is.numeric(srtRow)) + if(is.null(srtRow) || is.numeric(srtRow)) { xpd.orig <- par("xpd") par(xpd=NA) @@ -475,7 +486,8 @@ labels=labRow, adj=adjRow, cex=cexRow, - srt=srtRow + srt=srtRow, + col=colRow ) par(xpd=xpd.orig) } Modified: trunk/gplots/man/heatmap.2.Rd =================================================================== --- trunk/gplots/man/heatmap.2.Rd 2015-04-14 22:02:42 UTC (rev 1929) +++ trunk/gplots/man/heatmap.2.Rd 2015-04-22 21:33:06 UTC (rev 1930) @@ -71,6 +71,8 @@ adjCol = c(NA,0), offsetRow = 0.5, offsetCol = 0.5, + colRow = NULL, + colCol = NULL, # color key + density info key = TRUE, @@ -111,10 +113,11 @@ \code{\link{dendrogram}}, then it is used "as-is", ie without any reordering. If a vector of integers, then dendrogram is computed and reordered based on the order of the vector.} - \item{Colv}{determines if and how the \emph{column} dendrogram should be - reordered. Has the options as the \code{Rowv} argument above and - \emph{additionally} when \code{x} is a square matrix, \code{Colv = - "Rowv"} means that columns should be treated identically to the rows.} + \item{Colv}{determines if and how the \emph{column} dendrogram should + be reordered. Has the options as the \code{Rowv} argument above and + \emph{additionally} when \code{x} is a square matrix, + \code{Colv="Rowv"} means that columns should be treated identically + to the rows.} \item{distfun}{function used to compute the distance (dissimilarity) between both rows and columns. Defaults to \code{\link{dist}}.} \item{hclustfun}{function used to compute the hierarchical clustering @@ -128,7 +131,8 @@ reordering the row and column dendrograms. The default uses \code{\link{stats}{reorder.dendrogram}} }. \item{symm}{logical indicating if \code{x} should be treated - \bold{symm}etrically; can only be true when \code{x} is a square matrix.} + \bold{symm}etrically; can only be true when \code{x} is a + square matrix.} % data scaling \item{scale}{character indicating if the values should be centered and scaled in either the row direction or the column direction, or @@ -150,12 +154,14 @@ \item{col}{colors used for the image. Defaults to heat colors (\code{heat.colors}).} % block separation - \item{colsep, rowsep, sepcolor}{(optional) vector of integers indicating - which columns or rows should be separated from the preceding columns - or rows by a narrow space of color \code{sepcolor}.} - \item{sepwidth}{(optional) Vector of length 2 giving the width (colsep) or height (rowsep) the separator box - drawn by colsep and rowsep as a function of the width (colsep) or - height (rowsep) of a cell. Defaults to \code{c(0.05, 0.05)}} + \item{colsep, rowsep, sepcolor}{(optional) vector of integers + indicating which columns or rows should be separated from the + preceding columns or rows by a narrow space of color + \code{sepcolor}.} + \item{sepwidth}{(optional) Vector of length 2 giving the width + (colsep) or height (rowsep) the separator box drawn by colsep and + rowsep as a function of the width (colsep) or height (rowsep) of a + cell. Defaults to \code{c(0.05, 0.05)}} % cell labeling \item{cellnote}{(optional) matrix of character strings which will be placed within each color cell, e.g. p-value symbols.} @@ -181,25 +187,31 @@ defaults to the value of \code{tracecol}.} % Row/Column Labeling \item{margins}{numeric vector of length 2 containing the margins - (see \code{\link{par}(mar= *)}) for column and row names, respectively.} - \item{ColSideColors}{(optional) character vector of length \code{ncol(x)} - containing the color names for a horizontal side bar that may be used to - annotate the columns of \code{x}.} - \item{RowSideColors}{(optional) character vector of length \code{nrow(x)} - containing the color names for a vertical side bar that may be used to - annotate the rows of \code{x}.} + (see \code{\link{par}(mar= *)}) for column and row names, + respectively.} + \item{ColSideColors}{(optional) character vector of length + \code{ncol(x)} containing the color names for a horizontal side bar + that may be used to annotate the columns of \code{x}.} + \item{RowSideColors}{(optional) character vector of length + \code{nrow(x)} containing the color names for a vertical side bar + that may be used to annotate the rows of \code{x}.} \item{cexRow, cexCol}{positive numbers, used as \code{cex.axis} in for the row or column axis labeling. The defaults currently only use number of rows or columns, respectively.} \item{labRow, labCol}{character vectors with row and column labels to use; these default to \code{rownames(x)} or \code{colnames(x)}, respectively.} - \item{srtRow, srtCol}{angle of row/column labels, in degrees from horizontal} + \item{srtRow, srtCol}{angle of row/column labels, in degrees from + horizontal} \item{adjRow, adjCol}{2-element vector giving the (left-right, top-bottom) justification of row/column labels (relative to the text - orientation).} - \item{offsetRow, offsetCol}{Number of character-width spaces to place - between row/column labels and the edge of the plotting region.} + orientation).} + \item{offsetRow, offsetCol}{Number of character-width spaces to + place between row/column labels and the edge of the plotting + region.} + \item{colRow, colCol}{color of row/column labels, either a scalar to + set the color of all labels the same, or a vector providing the + colors of each label item} % Color key and density info \item{key}{logical indicating whether a color-key should be shown.} \item{keysize}{numeric value indicating the size of the key} @@ -226,8 +238,8 @@ the xaxis of the color key. Returns a named list containing parameters that can be passed to \code{axis}. See examples.} \item{key.ytickfun}{function computing tick location and labels for - the y axis of the color key. Returns a named list containing - parameters that can be passed to \code{axis}. See examples.} + the y axis of the color key. Returns a named list containing + parameters that can be passed to \code{axis}. See examples.} \item{key.par}{graphical parameters for the color key. Named list that can be passed to \code{par}.} % plot labels @@ -446,14 +458,19 @@ RowSideColors=rc, ColSideColors=cc, margin=c(5, 10), xlab="specification variables", ylab= "Car Models", main="heatmap(<Mtcars data>, ..., scale=\"column\")", - tracecol="green", density="density") + tracecol="green", density="density") ## Note that the breakpoints are now symmetric about 0 + + ## Color the labels to match RowSideColors and ColSideColors + hv <- heatmap.2(x, col=cm.colors(255), scale="column", + RowSideColors=rc, ColSideColors=cc, margin=c(5, 10), + xlab="specification variables", ylab= "Car Models", + main="heatmap(<Mtcars data>, ..., scale=\"column\")", + tracecol="green", density="density", colRow=rc, colCol=cc, + srtCol=45, adjCol=c(0.5,1)) + - - - - %% want example using the `add.exp' argument! data(attitude) This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-04-22 21:35:26
|
Revision: 1931 http://sourceforge.net/p/r-gregmisc/code/1931 Author: warnes Date: 2015-04-22 21:35:19 +0000 (Wed, 22 Apr 2015) Log Message: ----------- Update DESCRIPTION, ChangeLog, and NEWS for gplots 2.17.0 Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/inst/ChangeLog trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2015-04-22 21:33:06 UTC (rev 1930) +++ trunk/gplots/DESCRIPTION 2015-04-22 21:35:19 UTC (rev 1931) @@ -4,8 +4,8 @@ Depends: R (>= 3.0) Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS -Version: 2.16.0 -Date: 2015-01-02 +Version: 2.17.0 +Date: 2015-04-21 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Modified: trunk/gplots/inst/ChangeLog =================================================================== --- trunk/gplots/inst/ChangeLog 2015-04-22 21:33:06 UTC (rev 1930) +++ trunk/gplots/inst/ChangeLog 2015-04-22 21:35:19 UTC (rev 1931) @@ -1,3 +1,33 @@ +2015-04-22 warnes + + * [r1930] R/heatmap.2.R, man/heatmap.2.Rd: heatmap.2: add new + 'colRow' and 'colCol' arguments to control the color of row and + column text labels + +2015-04-06 warnes + + * [r1916] inst/ChangeLog: Add ChangeLog files to repository + +2015-01-02 warnes + + * [r1913] DESCRIPTION, inst/NEWS: Update for gplots release 2.16.0. + * [r1912] R/plotmeans.R: Change default group count lable back to + 'n='. + * [r1911] R/plotmeans.R, man/plotmeans.Rd: - plotmeans: Pass + optional graphical arguments captured in '...' axis function + used to draw the x axis. + - plotmeans: Add an new argument 'text.n.label' to specify the + text + used for labelingthe number of elements in a group. + * [r1910] R/plotmeans.R: - Remove S-Plus-specific code + - Simplify model frame code + +2014-12-03 warnes + + * [r1909] tests/heatmap2Test.Rout.save: Update stored test output + to account for new startup message from KernSmooth package + * [r1908] DESCRIPTION: Fix package title capitalization. + 2014-12-02 warnes * [r1907] inst/NEWS: Add descrioption of node stack overflow issue Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2015-04-22 21:33:06 UTC (rev 1930) +++ trunk/gplots/inst/NEWS 2015-04-22 21:35:19 UTC (rev 1931) @@ -1,3 +1,12 @@ +Release 2.17.0 - 2015-04-21 +--------------------------- + +New Features: + +- heatmap.2() has two new arguments, 'colRow' and 'colCol' to control + the color of row and column text labels. + + Release 2.16.0 - 2015-01-02 --------------------------- 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:58:51
|
Revision: 1942 http://sourceforge.net/p/r-gregmisc/code/1942 Author: warnes Date: 2015-04-23 19:58:44 +0000 (Thu, 23 Apr 2015) Log Message: ----------- - The returned object from venn() now includes a 'interesection' attribution containing a list of which items are in each set intersection. This can be turned off by settting 'intersection=FALSE'. Modified Paths: -------------- trunk/gplots/R/venn.R trunk/gplots/man/venn.Rd Modified: trunk/gplots/R/venn.R =================================================================== --- trunk/gplots/R/venn.R 2015-04-23 19:09:17 UTC (rev 1941) +++ trunk/gplots/R/venn.R 2015-04-23 19:58:44 UTC (rev 1942) @@ -1,7 +1,7 @@ # This code plots Venn Diagrams for up to 5 sets. The # function getVennCounts is passed a list of vectors. # This is transformed into a table indicating the -# number of members for each intersection. This table +# number of intersections for each intersection. This table # is generated for any number of sets. # The function drawVennDiagram plots circles (up to three @@ -23,16 +23,19 @@ stop("Only indicator columns permitted") l <- lapply( l, function(x) which(as.logical(x))) - getVennCounts.list(l) + getVennCounts.list(l, universe=universe, verbose=verbose) } # l offers a list of arrays, their values are to # be tested for the size of their intersects. -getVennCounts.list<-function(l, universe=NA, verbose=F) { +getVennCounts.list<-function(l, universe=NA, verbose=F, intersections=TRUE) { if (verbose) cat("Interpreting data as list.\n") numSets<-length(l) result.table<-NULL result.table.names<-NULL + + memberList <- list() + # Iteration over all possible intersections involving all sets # or the complement (negation) of those sets. for (i in 0:(-1 + 2^numSets)) { @@ -104,8 +107,12 @@ sel<-NULL } + r.name<-paste(i2,collapse="") + if (intersections) { + memberList[[r.name]] <- sel + } + r<-length(sel) - r.name<-paste(i2,collapse="") result.row<-c(r,i2) dim(result.row)<-c(1,length(result.row)) rownames(result.row)<-c(r.name) @@ -132,6 +139,9 @@ else{ colnames(result.table)<-c("num",names(l)) } + if (intersections) { + attr(result.table,"intersections") <- memberList + } class(result.table) <- "venn" return(result.table) } @@ -144,9 +154,10 @@ small=0.7, showSetLogicLabel=FALSE, simplify=FALSE, - show.plot=TRUE) + show.plot=TRUE, + intersections=TRUE) { - counts <- getVennCounts(data, universe=universe) + counts <- getVennCounts(data, universe=universe, intersections=intersections) if(show.plot) drawVennDiagram(data=counts, Modified: trunk/gplots/man/venn.Rd =================================================================== --- trunk/gplots/man/venn.Rd 2015-04-23 19:09:17 UTC (rev 1941) +++ trunk/gplots/man/venn.Rd 2015-04-23 19:58:44 UTC (rev 1942) @@ -7,14 +7,14 @@ } \usage{ venn(data, universe=NA, small=0.7, showSetLogicLabel=FALSE, - simplify=FALSE, show.plot=TRUE) + simplify=FALSE, show.plot=TRUE, intersections=TRUE) \method{plot}{venn}(x, y, ..., small=0.7, showSetLogicLabel=FALSE, simplify=FALSE) } \arguments{ \item{data,x}{Either a list list containing vectors of names or indices - of group members, or a data frame containing boolean indicators of - group membership (see below)} + of group intersections, or a data frame containing boolean indicators of + group intersectionship (see below)} \item{universe}{Subset of valid name/index elements. Values ignore values in code{data} not in this list will be ignored. Use \code{NA} to use all elements of \code{data} (the default).} @@ -25,13 +25,17 @@ should be omitted.} \item{show.plot}{Logical flag indicating whether the plot should be displayed. If false, simply returns the group count matrix.} + \item{intersections}{Logical flag indicating + if the returned object should have the attribute + "individuals.in.intersections" featuring for every set a list of + individuals that are assigned to it.} \item{y,...}{Ignored} } \details{ \code{data} should be either a named list of vectors containing character string names ("GeneAABBB", "GeneBBBCY", .., "GeneXXZZ") or - indexes of group members (1, 2, .., N), or a data frame containing - indicator variables (TRUE, FALSE, TRUE, ..) for group membership. + indexes of group intersections (1, 2, .., N), or a data frame containing + indicator variables (TRUE, FALSE, TRUE, ..) for group intersectionship. Group names will be taken from the component list element or column names. } @@ -39,7 +43,7 @@ Invisibly returns an object of class "venn", containing a matrix of all possible sets of groups, and the observed count of items belonging to each The fist column contains observed counts, subsequent columns - contain 0-1 indicators of group membership. + contain 0-1 indicators of group intersectionship. } \author{ Steffen Moeller \email{steffen\_mo...@gm...}, @@ -64,9 +68,9 @@ input <-list(GroupA,GroupB,GroupC,GroupD) input -venn(input) +tmp <- venn(input) +attr(tmp, "intersections") - ## ## Example using a list of item indexes belonging to the ## specified group. @@ -131,6 +135,14 @@ test <- function(x) (x \%in\% GroupA) & (x \%in\% GroupB) & !(x \%in\% GroupC) universe[ test(universe) ] +## +## Intriduced with gplots 2.16, the names of individuals for everz intersection +## is offered as an attribute to the retrun value. +## +a<-venn(list(1:5,3:8),show.plot=F,intersections=TRUE) +intersections<-attr(a,"intersections") +print(intersections) + } \keyword{hplot} This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-04-23 22:55:45
|
Revision: 1954 http://sourceforge.net/p/r-gregmisc/code/1954 Author: warnes Date: 2015-04-23 22:55:43 +0000 (Thu, 23 Apr 2015) Log Message: ----------- In heatmap.2(), the color key now properly handles color breaks that are not equally spaced. (Issue reported by Tim Richter-Heitmann.) Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/R/heatmap.2.R trunk/gplots/inst/ChangeLog trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2015-04-23 22:49:10 UTC (rev 1953) +++ trunk/gplots/DESCRIPTION 2015-04-23 22:55:43 UTC (rev 1954) @@ -5,7 +5,7 @@ Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS Version: 2.17.0 -Date: 2015-04-21 +Date: 2015-04-23 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2015-04-23 22:49:10 UTC (rev 1953) +++ trunk/gplots/R/heatmap.2.R 2015-04-23 22:55:43 UTC (rev 1954) @@ -198,8 +198,8 @@ nr <- length(rowInd) } else if (is.integer(Rowv)) - { ## Compute dendrogram and do reordering based on given vector - browser() + { + ## Compute dendrogram and do reordering based on given vector distr <- distfun(x) hcr <- hclustfun(distr) ddr <- as.dendrogram(hcr) @@ -641,7 +641,7 @@ max.raw <- max.breaks } - z <- seq(min.raw, max.raw, length=length(col)) + z <- seq(min.raw, max.raw, by=min(diff(breaks)/4)) image(z=matrix(z, ncol=1), col=col, breaks=tmpbreaks, xaxt="n", yaxt="n") @@ -670,10 +670,11 @@ if(density.info=="density") { - dens <- density(x, adjust=densadj, na.rm=TRUE) + dens <- density(x, adjust=densadj, na.rm=TRUE, + from=min.scale, to=max.scale) omit <- dens$x < min(breaks) | dens$x > max(breaks) - dens$x <- dens$x[-omit] - dens$y <- dens$y[-omit] + dens$x <- dens$x[!omit] + 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) if (is.null(key.ytickfun)) { Modified: trunk/gplots/inst/ChangeLog =================================================================== --- trunk/gplots/inst/ChangeLog 2015-04-23 22:49:10 UTC (rev 1953) +++ trunk/gplots/inst/ChangeLog 2015-04-23 22:55:43 UTC (rev 1954) @@ -1,5 +1,36 @@ +2015-04-23 warnes + + * [r1948] R/plotCI.R: - plotCI() was not properly respecting the + 'type=' argument. This has + been corrected. + * [r1947] R/overplot.R: - Remove stray browser() call from + overplot() + * [r1943] man/balloonplot.Rd: Explicitly specify argument to + gplots:::reorder.factor to prevent error. + * [r1942] R/venn.R, man/venn.Rd: - The returned object from venn() + now includes a 'interesection' + attribution containing a list of which items are in each set + intersection. This can be turned off by settting + 'intersection=FALSE'. + * [r1941] R/heatmap.2.R: 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"). + * [r1940] R/heatmap.2.R: In heatmap.2() split calls to distfun() + and hclustfun() into separate steps to make debugging easier + 2015-04-22 warnes + * [r1931] DESCRIPTION, inst/ChangeLog, inst/NEWS: Update + DESCRIPTION, ChangeLog, and NEWS for gplots 2.17.0 * [r1930] R/heatmap.2.R, man/heatmap.2.Rd: heatmap.2: add new 'colRow' and 'colCol' arguments to control the color of row and column text labels Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2015-04-23 22:49:10 UTC (rev 1953) +++ trunk/gplots/inst/NEWS 2015-04-23 22:55:43 UTC (rev 1954) @@ -1,4 +1,4 @@ -Release 2.17.0 - 2015-04-21 +Release 2.17.0 - 2015-04-23 --------------------------- New Features: @@ -6,7 +6,30 @@ - heatmap.2() has two new arguments, 'colRow' and 'colCol' to control the color of row and column text labels. +- heatmap.2() has been modified to make it easier to extract and plot + subclusters from a large heatmap. Simply pass the dendrogram 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. (Patch contributed by Ilia Kats.) +- venn() now returns a list of the members of each set intersection in + the attribute 'intersections'. This can be disabled using the + argument 'intersection=FALSE' (Patch by Steffen Möller.) + +Bug Fixes: + +- plotCI() now properly respects the 'type=' argument. (Bug report + and correction by Wiktor Żelazny.) + +- Remove stray browser() call from overplot() + +- In the balloonplot() examples, explicitly specify argument to + gplots:::reorder.factor to prevent error. + +Other Changes: + +- Remove stray browser() call from + Release 2.16.0 - 2015-01-02 --------------------------- 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:25:33
|
Revision: 1994 http://sourceforge.net/p/r-gregmisc/code/1994 Author: warnes Date: 2015-05-01 15:25:31 +0000 (Fri, 01 May 2015) Log Message: ----------- - heatmap.2: column traces could be plotted in the wrong order. - heatmap.2: add support for plotting sub-clusters of the full row and column dendrograms Modified Paths: -------------- trunk/gplots/R/heatmap.2.R trunk/gplots/man/heatmap.2.Rd Modified: trunk/gplots/R/heatmap.2.R =================================================================== --- trunk/gplots/R/heatmap.2.R 2015-04-29 03:31:55 UTC (rev 1993) +++ trunk/gplots/R/heatmap.2.R 2015-05-01 15:25:31 UTC (rev 1994) @@ -200,7 +200,7 @@ else if (is.integer(Rowv)) { ## Compute dendrogram and do reordering based on given vector - distr <- distfun(x) + distr <- distfun(x) hcr <- hclustfun(distr) ddr <- as.dendrogram(hcr) ddr <- reorderfun(ddr, Rowv) @@ -291,10 +291,10 @@ labCol <- if(is.null(colnames(x))) (1:nc)[colInd] else colnames(x) else labCol <- labCol[colInd] - + if(!is.null(colRow)) colRow <- colRow[rowInd] - + if(!is.null(colCol)) colCol <- colCol[colInd] @@ -536,7 +536,7 @@ { retval$vline <- vline vline.vals <- scale01(vline, min.scale, max.scale) - for( i in colInd ) + for( i in 1:length(colInd) ) { if(!is.null(vline)) { Modified: trunk/gplots/man/heatmap.2.Rd =================================================================== --- trunk/gplots/man/heatmap.2.Rd 2015-04-29 03:31:55 UTC (rev 1993) +++ trunk/gplots/man/heatmap.2.Rd 2015-05-01 15:25:31 UTC (rev 1994) @@ -115,7 +115,7 @@ computed and reordered based on the order of the vector.} \item{Colv}{determines if and how the \emph{column} dendrogram should be reordered. Has the options as the \code{Rowv} argument above and - \emph{additionally} when \code{x} is a square matrix, + \emph{additionally} when \code{x} is a square matrix, \code{Colv="Rowv"} means that columns should be treated identically to the rows.} \item{distfun}{function used to compute the distance (dissimilarity) @@ -131,7 +131,7 @@ reordering the row and column dendrograms. The default uses \code{\link{stats}{reorder.dendrogram}} }. \item{symm}{logical indicating if \code{x} should be treated - \bold{symm}etrically; can only be true when \code{x} is a + \bold{symm}etrically; can only be true when \code{x} is a square matrix.} % data scaling \item{scale}{character indicating if the values should be centered and @@ -154,7 +154,7 @@ \item{col}{colors used for the image. Defaults to heat colors (\code{heat.colors}).} % block separation - \item{colsep, rowsep, sepcolor}{(optional) vector of integers + \item{colsep, rowsep, sepcolor}{(optional) vector of integers indicating which columns or rows should be separated from the preceding columns or rows by a narrow space of color \code{sepcolor}.} @@ -187,12 +187,12 @@ defaults to the value of \code{tracecol}.} % Row/Column Labeling \item{margins}{numeric vector of length 2 containing the margins - (see \code{\link{par}(mar= *)}) for column and row names, + (see \code{\link{par}(mar= *)}) for column and row names, respectively.} - \item{ColSideColors}{(optional) character vector of length + \item{ColSideColors}{(optional) character vector of length \code{ncol(x)} containing the color names for a horizontal side bar that may be used to annotate the columns of \code{x}.} - \item{RowSideColors}{(optional) character vector of length + \item{RowSideColors}{(optional) character vector of length \code{nrow(x)} containing the color names for a vertical side bar that may be used to annotate the rows of \code{x}.} \item{cexRow, cexCol}{positive numbers, used as \code{cex.axis} in @@ -206,8 +206,8 @@ \item{adjRow, adjCol}{2-element vector giving the (left-right, top-bottom) justification of row/column labels (relative to the text orientation).} - \item{offsetRow, offsetCol}{Number of character-width spaces to - place between row/column labels and the edge of the plotting + \item{offsetRow, offsetCol}{Number of character-width spaces to + place between row/column labels and the edge of the plotting region.} \item{colRow, colCol}{color of row/column labels, either a scalar to set the color of all labels the same, or a vector providing the @@ -329,7 +329,6 @@ \seealso{\code{\link{image}}, \code{\link{hclust}}} \examples{ - library(gplots) data(mtcars) x <- as.matrix(mtcars) rc <- rainbow(nrow(x), start=0, end=.3) @@ -338,20 +337,26 @@ ## ## demonstrate the effect of row and column dendrogram options ## - heatmap.2(x) ## default - dendrogram plotted and reordering done. + heatmap.2(x) ## default - dendrogram plotted and reordering done. heatmap.2(x, dendrogram="none") ## no dendrogram plotted, but reordering done. - heatmap.2(x, dendrogram="row") ## row dendrogram plotted and row reordering done. - heatmap.2(x, dendrogram="col") ## col dendrogram plotted and col reordering done. + heatmap.2(x, dendrogram="row") ## row dendrogram plotted and row reordering done. + heatmap.2(x, dendrogram="col") ## col dendrogram plotted and col reordering done. - heatmap.2(x, keysize=2) ## default - dendrogram plotted and reordering done. + heatmap.2(x, keysize=2) ## default - dendrogram plotted and reordering done. - heatmap.2(x, Rowv=FALSE, dendrogram="both") ## generate warning! - heatmap.2(x, Rowv=NULL, dendrogram="both") ## generate warning! - heatmap.2(x, Colv=FALSE, dendrogram="both") ## generate warning! + heatmap.2(x, Rowv=FALSE, dendrogram="both") ## generates a warning! + heatmap.2(x, Rowv=NULL, dendrogram="both") ## generates a warning! + heatmap.2(x, Colv=FALSE, dendrogram="both") ## generates a warning! ## Reorder dendrogram by branch means rather than sums heatmap.2(x, reorderfun=function(d, w) reorder(d, w, agglo.FUN = mean) ) + ## plot a sub-cluster using the same color coding as for the full heatmap + full <- heatmap.2(x) + heatmap.2(x, Colv=full$colDendrogram[[2]], breaks=full$breaks) # column subset + heatmap.2(x, Rowv=full$rowDendrogram[[1]], breaks=full$breaks) # row subset + heatmap.2(x, Colv=full$colDendrogram[[2]], + Rowv=full$rowDendrogram[[1]], breaks=full$breaks) # both ## Show effect of row and column label rotation heatmap.2(x, srtCol=NULL) @@ -460,7 +465,7 @@ main="heatmap(<Mtcars data>, ..., scale=\"column\")", tracecol="green", density="density") ## Note that the breakpoints are now symmetric about 0 - + ## Color the labels to match RowSideColors and ColSideColors hv <- heatmap.2(x, col=cm.colors(255), scale="column", RowSideColors=rc, ColSideColors=cc, margin=c(5, 10), @@ -468,9 +473,9 @@ main="heatmap(<Mtcars data>, ..., scale=\"column\")", tracecol="green", density="density", colRow=rc, colCol=cc, srtCol=45, adjCol=c(0.5,1)) - + %% want example using the `add.exp' argument! data(attitude) 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:34:21
|
Revision: 1996 http://sourceforge.net/p/r-gregmisc/code/1996 Author: warnes Date: 2015-05-01 15:34:19 +0000 (Fri, 01 May 2015) Log Message: ----------- Update DESCRIPTION, NEWS, and ChangeLog again for gplots 2.17.0. Modified Paths: -------------- trunk/gplots/DESCRIPTION trunk/gplots/inst/ChangeLog trunk/gplots/inst/NEWS Modified: trunk/gplots/DESCRIPTION =================================================================== --- trunk/gplots/DESCRIPTION 2015-05-01 15:28:33 UTC (rev 1995) +++ trunk/gplots/DESCRIPTION 2015-05-01 15:34:19 UTC (rev 1996) @@ -5,11 +5,11 @@ Imports: gtools, gdata, stats, caTools, KernSmooth Suggests: grid, MASS Version: 2.17.0 -Date: 2015-04-23 +Date: 2015-05-01 Author: Gregory R. Warnes, Ben Bolker, Lodewijk Bonebakker, Robert Gentleman, Wolfgang Huber Andy Liaw, Thomas Lumley, Martin Maechler, Arni Magnusson, Steffen Moeller, Marc Schwartz, Bill Venables Maintainer: Gregory R. Warnes <gr...@wa...> License: GPL-2 -NeedsCompilation: No +NeedsCompilation: no Modified: trunk/gplots/inst/ChangeLog =================================================================== --- trunk/gplots/inst/ChangeLog 2015-05-01 15:28:33 UTC (rev 1995) +++ trunk/gplots/inst/ChangeLog 2015-05-01 15:34:19 UTC (rev 1996) @@ -1,5 +1,16 @@ +2015-05-01 warnes + + * [r1995] R/heatmap.2.R: - heatmap.2: row traces could be plotted + in the wrong order. + * [r1994] R/heatmap.2.R, man/heatmap.2.Rd: - heatmap.2: column + traces could be plotted in the wrong order. + - heatmap.2: add support for plotting sub-clusters of the full + row and + column dendrograms + 2015-04-23 warnes + * [r1955] inst/ChangeLog, inst/NEWS: Update NEWS and ChangeLog * [r1954] DESCRIPTION, R/heatmap.2.R, inst/ChangeLog, inst/NEWS: In heatmap.2(), the color key now properly handles color breaks that are not equally spaced. (Issue reported by Tim Richter-Heitmann.) Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2015-05-01 15:28:33 UTC (rev 1995) +++ trunk/gplots/inst/NEWS 2015-05-01 15:34:19 UTC (rev 1996) @@ -11,7 +11,7 @@ subclusters from a large heatmap. Simply pass the dendrogram 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. (Patch contributed by Ilia Kats.) + scaling. (Suggestion and patch contributed by Ilia Kats.) - venn() now returns a list of the members of each set intersection in the attribute 'intersections'. This can be disabled using the @@ -22,6 +22,9 @@ - In heatmap.2(), the color key now properly handles color breaks that are not equally spaced. (Issue reported by Tim Richter-Heitmann.) +- In heatmap.2(), row/column traces in could be plotted on the wrong + row/column. + - plotCI() now properly respects the 'type=' argument. (Bug report and correction by Wiktor Żelazny.) This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |
From: <wa...@us...> - 2015-05-01 17:48:29
|
Revision: 2008 http://sourceforge.net/p/r-gregmisc/code/2008 Author: warnes Date: 2015-05-01 17:48:26 +0000 (Fri, 01 May 2015) Log Message: ----------- Update NEWS again. Modified Paths: -------------- trunk/gplots/NAMESPACE trunk/gplots/inst/NEWS Modified: trunk/gplots/NAMESPACE =================================================================== --- trunk/gplots/NAMESPACE 2015-05-01 17:47:42 UTC (rev 2007) +++ trunk/gplots/NAMESPACE 2015-05-01 17:48:26 UTC (rev 2008) @@ -3,8 +3,8 @@ bandplot, barplot2, bluered, + boxplot.n, boxplot2, - boxplot.n, ci2d, col2hex, colorpanel, Modified: trunk/gplots/inst/NEWS =================================================================== --- trunk/gplots/inst/NEWS 2015-05-01 17:47:42 UTC (rev 2007) +++ trunk/gplots/inst/NEWS 2015-05-01 17:48:26 UTC (rev 2008) @@ -35,10 +35,13 @@ Other Changes: -- smartlegend() is now marked as deprecated, since the relative - positioning feature ('top', 'right') has been added to - graphics::legend() +- smartlegend() is now deprecated because the relative positioning + feature ('top', 'right') has been added to graphics::legend(). + Calling smartlegend() will generate a warning. +- boxplot.n() and plot.lm2() are defunct have been removed. Use of + these functions will now generate an error. + - Update out-of-date URLs in man pages. Release 2.16.0 - 2015-01-02 This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |