diff --git a/DESCRIPTION b/DESCRIPTION new file mode 100644 index 0000000..187238b --- /dev/null +++ b/DESCRIPTION @@ -0,0 +1,19 @@ +Package: squash +Version: 1.0.1 +Date: 2011-08-15 +Title: Color-based plots for multivariate visualization +Author: Aron Eklund +Maintainer: Aron Eklund +Depends: grDevices +Description: This package provides functions for color-based + visualization of multivariate data, i.e. colorgrams or + heatmaps. Lower-level functions are provided to map numeric + values to colors, display a matrix as an array of colors, and + draw color keys. Higher-level plotting functions are provided + to generate a bivariate histogram, a dendrogram aligned with a + color-coded matrix, a triangular distance matrix, and more. +License: Artistic-2.0 +URL: http://www.cbs.dtu.dk/~eklund/squash/ +Packaged: 2012-10-29 08:59:49 UTC; ripley +Repository: CRAN +Date/Publication: 2012-10-29 08:59:49 diff --git a/MD5 b/MD5 new file mode 100644 index 0000000..380695a --- /dev/null +++ b/MD5 @@ -0,0 +1,23 @@ +5edde01db53920785ab64fa964449afb *DESCRIPTION +6dbf5337a68b3906b42c512850aa973c *NAMESPACE +901118a222919be6fe3036ca95359e18 *NEWS +df5ecd94bce28dd57ce098b2456a400d *R/distogram.R +924597a1476cdd0f705eccde4797aa24 *R/squash.R +4939e0848ba78f083371cc51179f2000 *man/ColorPalettes.Rd +f7ea3726e2d458adc83260319d1ab8ef *man/cimage.Rd +11b8be856db2849fbc8ff4c1943850ae *man/cmap.Rd +a872f24a0494ed79599773bfdad56867 *man/colorgram.Rd +e83e81481241ce5651dba79c2642319f *man/corrogram.Rd +0a5616faaa5896b6e0f6d2deb15262bd *man/dendromat.Rd +f761c12896121179aba382303b418aec *man/diamond.Rd +1b52082a0e2e248e62a5624c8f052777 *man/distogram.Rd +62d384871fc3fd0056da717f8c01876d *man/hist2.Rd +ac1864eebb9c47bb398a7278481a40fd *man/hkey.Rd +310aa50eda0769de6a794043499c2b30 *man/makecmap.Rd +5a7eb8b7bc8ef220e793b97b1637fb92 *man/matapply.Rd +d1dec50054bc2880f9dbaf3972808556 *man/prettyInt.Rd +c6ceaba828c5db7b2ab8d78aef8d8c49 *man/savemat.Rd +7a7f36999bb0a5cf9ea49ad73f52b847 *man/squashgram.Rd +7a848b30dd989f0a1f933f3761f52cc4 *man/trianglegram.Rd +23137457888be0df19d17511c72d44fe *man/xyzmat.coords.Rd +a91a61521429f5efc2f235cccea0f99a *man/xyzmat2xyz.Rd diff --git a/NAMESPACE b/NAMESPACE new file mode 100644 index 0000000..174ff74 --- /dev/null +++ b/NAMESPACE @@ -0,0 +1,10 @@ +# Default NAMESPACE created by R +# Remove the previous line if you edit this file + +# Export all names +exportPattern(".") + +# Import all packages listed as Imports or Depends +import( + grDevices +) diff --git a/NEWS b/NEWS new file mode 100644 index 0000000..84d743b --- /dev/null +++ b/NEWS @@ -0,0 +1,192 @@ +Squash NEWS + + +Changes in version 1.0.1 (2011-08-15) + +- First CRAN release +- "hist2" now has a new argument "breaks", which defaults to "prettyInt" +- Fixed bug in "cimage" in which axes were plotted when add=TRUE +- Fixed bug in "makecmap" causing domain extension into positive numbers when x is all negative +- Fixed bug in which "prettyLog" could return only a single value +- Add check for zero-length x in "prettyInt" and "prettyLog" to match behavior of "pretty" +- "prettyInt" now performs better when x includes all of {zero, negative numbers, positive numbers} +- In "makecmap", the old argument "center" is now called "symm" (for symmetric) +- "makecmap" gets a ... argument, passed to "breaks" +- "dendromat" now ends with par(usr) set to c(0,1,0,1)) instead of something unpredictable; this should make legend placement a bit easier. +- "dendromat" now ends by resetting the clipping region, so "vkey" can be used afterwards. + + +Changes in version 1.0.0 (2011-08-11) + +- MAJOR update, with several function names *changed* to improve clarity; sorry for any inconvenience +- The previous "colormap" is now called "makecmap" +- The previous "num2col" is now called "cmap" +- The previous "raster" is now called "cimage" +- The option "trueRaster" is now called "useRaster" for consistency with the standard function "image". +- Remove the old "orangeblue" +- The old "orangeblue2" is now "blueorange" +- The old "darkredblue" is slightly adjusted to make the extremes distinguishable and is now called "darkbluered" +- New color palette "bluered". +- The old function "squash" is now called "matapply" +- The old function "mat2bm" is now called "savemat" +- Improvements in automatic axis naming in squashgram and matapply + + +Changes in version 0.4.4 (2011-08-09) + +- Documentation improvements. +- Rename "pretty.log" -> "prettyLog" to avoid S3 method warnings +- Rename "pretty.int" -> "prettyInt" +- Added argument "do.dev.off" to function "mat2bm" +- 'squashgram' now uses xyz.coords, which can change the automatic axis labels +- Some 'squash', 'squashgram', and 'hist2' parameters are now NULL by default: xlim, ylim, xbreaks, ybreaks +- 'raster' now takes arguments 'xlabels', 'ylabels', and 'axes' +- Removed the mostly useless functions 'raster2' and 'colorgram2' + + +Changes in version 0.4.3 (2011-02-21) + +- "dendromat" now looks for names in argument "x" if "labRow" is NULL. + + +Changes in version 0.4.2 (2010-11-01) + +- Added function "raster2"; like "raster" but with categorical axes. +- Added function "colorgram2"; like "colorgram" but with categorical axes. + + +Changes in version 0.4.1 (2010-10-26) + +- Replace "xyz.coords.matrix" with "xyzmat.coords" and "xyzmat2xyz". +- "raster" and "colorgram" now use "xyzmat.coords" as front end for input. +- Fix bug in "colormap" that could cause errors when pretty.log is used with negative values. +- Remove function "pretty.auto" +- New argument "small" in "pretty.log" +- "pretty.log" now deals with negative numbers +- Fixed bug in "pretty.log" that caused it to overshoot the maximum. +- New color palette "coolheat" + + +Changes in version 0.4.0 (2010-10-21) + +- Several major changes! +- Modify "raster" to optionally use the (relatively) new "rasterImage" function from "graphics" package. +- Replace function "matpng" with new function "mat2bm", which works better and supports a few other graphics devices. +- Added function "xyz.coords.matrix". +- "squash" now accepts a matrix as input, using xyz.coords.matrix +- The former "minikey2h" and "minikey2v" have been replaced by "hkey" and "vkey", which are similar but have slightly different arguments +- Remove functions "minikey", "keyPlus", and "drawKey" +- "colorgram" and "distogram" updated to call hkey and vkey +- Replaced function "triplotCol" with "trianglegram", which now accepts new arguments. +- "raster" and "colorgram" no longer accept labels (character) for x and y + + +Changes in version 0.3.1 (2009-11-04) + +- Added function "matpng". + + +Changes in version 0.3.0 (2009-07-21) + +- Added function "orangeblue2" +- Change name of "pretty.pseudolog" to "pretty.log". +- "pretty.int" was broken in several ways, but should be fixed now. +- Removed "pretty.count". +- Added function "pretty.auto". +- "colorgram" now works differently: 1. The parameter "key" now takes numeric values to specify the type of key. 2. Removed parameter "key.width". 3. Added parameter "key.args". + + +Changes in version 0.2.3 (2009-07-18) + +- New functions "minikey2h" and "minikey2v". +- Changed the name of this file to "NEWS" (was "ChangeLog"). + + +Changes in version 0.2.2 (2009-05-05) + +- Revert many of the changes to "colormap" made in v. 0.2.0. +- Modified the "pretty.*" functions. +- Removed "int" argument from "colorgram". +- Many other fixes and updates. +- Remove "legend.map". + + +Changes in version 0.2.1 (2009-05-05) + +- Added arguments (xaxp, yaxp, xaxt, yaxt, bty, las) to "raster". +- Added function "pretty.count" and "pretty.pseudolog". + + +Changes in version 0.2.0 (2009-03-05) + +- "colormap" now returns additional list items "n", "center", "equal", "type". +- In "colormap", "x" can be omitted if breakpoints are specified. +- In "colormap", new parameters: "int", "col.zero". +- "Colormap" now can do "integer-based" maps. +- In "colormap", defaults for "right" is now TRUE, which matches the defaults for "cut". (Originally, it was the other way around because this made more sense for integers). +- Added helper functions "pretty.int", "integer.intervals". +- Documentation fixes. +- Added arguments to "dendromat": "border", "cex.lab" (suggested by Chris Workman). +- Added "gap" argument to "dendromat". +- Change "triplotCol" so it only adjusts the right-hand margin by default (and not the other margins). + + +Changes in version 0.1.9 (2008-12-16) + +- Adjust "triplotCol" such that labels fall on 1, 2, 3, ... instead of 1, 3, 5, ... +- Remove "line" parameter from "triplotCol", add "fix.mar" parameter. + + +Changes in version 0.1.8 (2008-12-12) + +- Minor documentation updates. +- Added "diamond", "distogram", "corrogram", "triplotCol", and "miniKey". + + +Changes in version 0.1.7 (2008-08-05) + +- Added color palette "darkredblue". + + +Changes in version 0.1.6 (2008-05-03) + +- Added function "dendromat". +- Misc. documentation fixes. + + +Changes in version 0.1.5 (2008-03-02) + +- Change "raster" to set up plot in normal way (i.e. with "plot"), and remove "..." argument, which was pretty much useless. +- Update "raster" to work work with non-evenly spaced breakpoints/midpoints and non-1 zsize. +- These changes also fix buggy behavior in raster. +- Misc. documentation fixes. + + +Changes in version 0.1.4 (2008-02-28) + +- Added "heat" as a new palette. +- Added "keyPlus" function. +- In "drawKey", changed default las.axis = 1 + + +Changes in version 0.1.3 (2008-02-26) + +- Documentation improvements. +- "squash" now uses "xyz.coords" for input, and returns additional list items "xlab", "ylab", and "zlab". +- Similarly, "hist2" now used "xy.coords". +- The argument in "colorgram" formerly called "key.lab" is now called "zlab", for compatibility with "persp". Also, "xlab" and "ylab" are specifically included in the argument list. +- "colorgram" and "raster" now try harder to assign dimension labels. +- "raster" is a bit more flexible with input (but still not ideal). + + +Changes in version 0.1.2 (2008-02-23) + +- A few documentation improvements. +- Several improvements to "drawKey": +- Added "digits" and "by" arguments to control axis formatting. +- Removed "at" argument (use "by" instead). +- Default "las.lab" argument is now 0. +- Default "las.axis" argument is now 2. +- "side" = 1 and "side" = 3 now work. +- By default (i.e., when "by" = NA), the function tries to avoid plotting axis labels on top of each other. + diff --git a/R/distogram.R b/R/distogram.R new file mode 100644 index 0000000..81191e2 --- /dev/null +++ b/R/distogram.R @@ -0,0 +1,81 @@ +# distogram.R +# +# Aron Eklund +# + + +diamond <- function(x, y = NULL, radius, ...) { + xy <- xy.coords(x, y) + xL <- xy$x - radius + xC <- xy$x + xR <- xy$x + radius + yB <- xy$y - radius + yC <- xy$y + yT <- xy$y + radius + n <- length(xL) + x2 <- rbind(rep.int(NA, n), xC, xL, xC, xR)[-1] + y2 <- rbind(rep.int(NA, n), yB, yC, yT, yC)[-1] + polygon(x2, y2, ...) +} + + +trianglegram <- function(x, labels = rownames(x), + lower = TRUE, diag = FALSE, right = FALSE, + add = FALSE, xpos = 0, ypos = 0, xlim, ylim, ...) { + if(nrow(x) != ncol(x)) + stop("x must be a square matrix") + n <- nrow(x) + if(lower) { + wh <- lower.tri(x, diag = diag) + } else { + wh <- upper.tri(x, diag = diag) + } + ## x1, y1 = unrotated coordinates + x1 <- col(x)[wh] + y1 <- row(x)[wh] + ## rotated coordinates + if(right) { + x2 <- ( y1 - x1) / 2 + y2 <- (x1 + y1) / 2 + } else { # right + x2 <- (- y1 + x1) / 2 + y2 <- (x1 + y1) / 2 + } + x2 <- x2 + xpos + y2 <- y2 + ypos + if(is.null(labels)) labels <- 1:n + if(!add) { + if(missing(xlim)) xlim <- c(-n/2, n/2) + xpos + if(missing(ylim)) ylim <- c(0.5, n + 0.5) + ypos + plot(xlim, ylim, type = 'n', + axes = FALSE, xlab = '', ylab = '', ...) + } + diamond(x2, y2, radius = 0.5, col = x[wh]) + if(diag) offset <- 0.5 else offset <- 0 + if(right) { + text(0, 1:n, labels = labels, pos = 2, offset = offset, xpd = NA) + } else { + text(0, 1:n, labels = labels, pos = 4, offset = offset, xpd = NA) + } +} + + +distogram <- function(x, map, n = 10, base = NA, colFn = heat, + key = TRUE, title = NA, ...) { + if(class(x) == 'dist') x <- as.matrix(x) + stopifnot(nrow(x) == ncol(x)) + if (missing(map)) { + map <- makecmap(x, n = n, base = base, colFn = colFn) + } + trianglegram(cmap(x, map = map), ...) + if(key) hkey(map = map, title = title) + invisible(map) +} + + +corrogram <- function(...) { + map <- makecmap(c(-1,1), n = 20, colFn = blueorange, include.lowest = TRUE) + distogram(..., map = map) +} + + diff --git a/R/squash.R b/R/squash.R new file mode 100644 index 0000000..e329aaa --- /dev/null +++ b/R/squash.R @@ -0,0 +1,580 @@ +# squash.R +# +# Aron Charles Eklund +# +# source("~/aron/chb/projects/R/packages/squash/R/squash.R") + + +######### color palettes ########### + +rainbow2 <- function(n) rainbow(n, end = 0.8) + +grayscale <- function(n, start = 0.9, end = 0) gray(seq(start, end, length = n)) + +greyscale <- grayscale + +blueorange <- colorRampPalette(c('blue', 'lightgrey', '#FF7A00'), interpolate = 'spline') + +bluered <- colorRampPalette(c('blue', 'lightgrey', 'red'), interpolate = 'spline') + +darkbluered <- colorRampPalette(c(rgb(0.1, 0.1, 0.4), grey(0.9), rgb(0.4, 0.1, 0.1)), interpolate = 'spline') + +jet <- colorRampPalette(c("#00007F", "blue", "#007FFF", "cyan", + "#7FFF7F", "yellow", "#FF7F00", "red", "#7F0000")) + +heat <- colorRampPalette(c('black', 'darkred', 'orange', 'yellow')) + +coolheat <- colorRampPalette(c('cyan', '#00A5FF', '#00008B', 'black', 'black', 'darkred', 'orange', 'yellow')) + + +######### essential color mapping functions ########### + +makecmap <- function(x, n = 10, + breaks = pretty, symm = FALSE, base = NA, + colFn = jet, col.na = NA, + right = FALSE, include.lowest = FALSE, ...) { + if(missing(x) && (missing(breaks) || !is.numeric(breaks))) + stop("either 'x' or numeric 'breaks' must be supplied") + if((missing(breaks) || !is.numeric(breaks))) { ## Need to calculate breakpoints + if (!is.numeric(x)) + stop("'x' must be numeric") + if(!is.na(base)) { + x <- log(x, base = base) + } + lim <- range(x, finite = TRUE) + if(lim[1] == lim[2]) { ## special case + if(right) { + breakpoints <- c(lim[1] - 1, lim[1]) + } else { + breakpoints <- c(lim[1], lim[1] + 1) + } + } else { ## end special case + if(!include.lowest) { + if(right) + lim[1] <- extendrange(r = lim, f = 0.001)[1] + else + lim[2] <- extendrange(r = lim, f = 0.001)[2] + } + if(symm) { + maxabs <- max(abs(lim)) + lim <- c(-maxabs, maxabs) + } + if(max(abs(lim)) > 0) + lim[3] <- sign(lim[1]) * min(abs(x)[x != 0]) ## include the smallest non-zero value in case "prettyLog" is used + breakpoints <- breaks(lim, n = n, ...) + if(!is.na(base)) { + breakpoints <- base ^ breakpoints + } + } + } else { ## Breakpoints are supplied + breakpoints = breaks + } + if (length(breakpoints) < 2) + stop("there must be at least two breakpoints") + if (any(duplicated(breakpoints))) + stop("breakpoints are not unique") + myColors <- colFn(length(breakpoints) - 1) + list(breaks = breakpoints, colors = myColors, + base = base, col.na = col.na, right = right, + include.lowest = include.lowest) +} + + +cmap <- function(x, map, outlier = NULL, ...) { + if(missing(map)) map <- makecmap(x, ...) + out.i <- cut(x, breaks = map$breaks, right = map$right, + include.lowest = map$include.lowest) + out <- map$colors[as.integer(out.i)] + dim(out) <- dim(x) + dimnames(out) <- dimnames(x) + names(out) <- names(x) + n.outliers <- sum(is.na(x) != is.na(out)) + if(n.outliers > 0) { + if (is.null(outlier)) + stop('Found ', n.outliers, ' values outside map range.') + else + warning(n.outliers, ' values outside map range will be colored ', outlier, '.') + out[is.na(x) != is.na(out)] <- outlier + } + out[is.na(x)] <- map$col.na + out +} + +######### functions similar to "pretty" ########### + +prettyInt <- function(x, n = 5, ...) { + x <- x[is.finite(x <- as.numeric(x))] + if (length(x) == 0L) return(x) + r <- range(x) + r.adj <- c(floor(r[1]), ceiling(r[2])) + p <- pretty(r.adj, n = n, ...) + sort(unique(as.integer(round(p)))) +} + +prettyLog <- function(x, n = 5, small = NA, + logrange = c(-100, 100)) { + x <- x[is.finite(x <- as.numeric(x))] + if (length(x) == 0L) return(x) + r <- range(x) + rmin <- range(abs(x[x != 0]), finite = TRUE)[1] + if(!is.na(small)) + rmin <- max(rmin, small) + expVals <- seq(logrange[1], logrange[2]) + ## narrow down candidate sequences one step at a time + cand <- list(base2 = c(1, 2, 5) * 10 ^ rep(expVals, each = 3), + base3 = c(1, 3) * 10 ^ rep(expVals, each = 2), + base10 = 10 ^ rep(expVals)) + cand2 <- lapply(cand, function(y) y[(which(y > rmin)[1] - 1):length(y)]) + cand3 <- lapply(cand2, function(y) c(sort(-y), 0, y)) + cand4 <- lapply(cand3, function(y) y[(which(y > r[1])[1] - 1):(which(y >= r[2])[1])]) + out.len <- sapply(cand4, length) + wh <- which.min(abs(out.len - n)) + cand5 <- cand4[[wh]] + if(length(cand5) == 1) { + if(cand5 > 0) return(c(0, cand5)) + if(cand5 < 0) return (c(cand5, 0)) + if(cand5 == 0) return (c(-1, 0)) + } else + return(cand5) +} + + +######### data manipulation functions ########### + +matapply <- function(x, y = NULL, z = NULL, FUN, + nx = 50, ny = nx, + xlim = NULL, ylim = NULL, + xbreaks = NULL, ybreaks = NULL, + right = FALSE, include.lowest = TRUE, ...) { + if(is.matrix(z) || (is.null(z) && is.matrix(x))) { + xyz <- xyzmat2xyz(x, y, z) + } else { + xyz <- xyz.coords(x, y, z) + } + if(is.null(xlim)) + xlim <- range(xyz$x, finite = TRUE) + if(is.null(ylim)) + ylim <- range(xyz$y, finite = TRUE) + if(is.null(xbreaks)) + xbreaks <- pretty(xlim, nx) + if(is.null(ybreaks)) + ybreaks <- pretty(ylim, ny) + xcut <- cut(xyz$x, breaks = xbreaks, + right = right, include.lowest = include.lowest) + ycut <- cut(xyz$y, breaks = ybreaks, + right = right, include.lowest = include.lowest) + z.out <- tapply(xyz$z, list(xcut, ycut), FUN, ...) + if(is.null(xyz$xlab)) xyz$xlab <- deparse(substitute(x)) + if(is.null(xyz$ylab)) xyz$ylab <- deparse(substitute(y)) + if(is.null(xyz$zlab)) xyz$zlab <- deparse(substitute(z)) + list(x = xbreaks, y = ybreaks, z = z.out, + xlab = xyz$xlab, ylab = xyz$ylab, + zlab = paste(deparse(substitute(FUN)), '(', xyz$zlab, ')', sep = '')) +} + + + +# returns custom "xyzmat.coords" from various types of input +xyzmat.coords <- function(x = NULL, y = NULL, z = NULL, + xlab = NULL, ylab = NULL, zlab = NULL, + xds = NULL, yds = NULL, zds = NULL) { + if(is.null(z)) { + if(is.matrix(x)) { + z <- x + if(is.null(zlab)) zlab <- xds + x <- NULL + } else if (is.list(x)) { + if(is.null(xlab)) + if(!is.null(x$xlab)) xlab <- x$xlab + else xlab <- paste(xds, 'x', sep = '$') + if(is.null(ylab)) + if(!is.null(x$ylab)) ylab <- x$ylab + else ylab <- paste(xds, 'y', sep = '$') + if(is.null(zlab)) + if(!is.null(x$zlab)) zlab <- x$zlab + else zlab <- paste(xds, 'z', sep = '$') + z <- x$z + y <- x$y + x <- x$x + } + } else if (is.null(y) && !is.null(x) && is.list(x)) { + if(is.null(xlab)) + if(!is.null(x$xlab)) xlab <- x$xlab + else xlab <- paste(xds, 'x', sep = '$') + if(is.null(ylab)) + if(!is.null(x$ylab)) ylab <- x$ylab + else ylab <- paste(xds, 'y', sep = '$') + y <- x$y + x <- x$x + } else { # z is specified, x and y maybe + if(is.null(xlab) && !is.null(x)) xlab <- xds + if(is.null(ylab) && !is.null(y)) ylab <- yds + if(is.null(zlab)) zlab <- zds + } + if(!is.matrix(z)) stop ("a matrix must be specified") + nr <- nrow(z) + nc <- ncol(z) + if(is.null(x)) { + x <- 1:nr + if(is.null(xlab)) xlab <- 'Row index' + } + if(is.null(y)) { + y <- 1:nc + if(is.null(ylab)) ylab <- 'Column index' + } + if(!length(x) %in% nr:(nr + 1)) + stop ("length of 'x' must be ", nr, " or ", nr + 1, " to match nrow(z)") + if(!length(y) %in% nc:(nc + 1)) + stop ("length of 'y' must be ", nc, " or ", nc + 1, " to match ncol(z)") + list(x = x, y = y, z = z, xlab = xlab, ylab = ylab, zlab = zlab) +} + +# returns standard "xyz.coords" from a matrix input +xyzmat2xyz <- function(...) { + m <- xyzmat.coords(...) + if(length(m$x) != nrow(m$z)) { + m$x <- 1:nrow(m$z) + warning("Cannot get x coordinates; using indices instead.") + } + if(length(m$y) != ncol(m$z)) { + m$y <- 1:ncol(m$z) + warning("Cannot get y coordinates; using indices instead.") + } + xyz.coords(x = m$x[row(m$z)], y = m$y[col(m$z)], z = as.vector(m$z), + xlab = m$xlab, ylab = m$ylab, zlab = m$zlab) +} + + + +######### plotting functions, sorted from low-level to high-level ########### +## (but not key-drawing functions, which are in the following section) + + +cimage <- function(x = NULL, y = NULL, zcol = NULL, zsize = 1, + xlab= NULL, ylab = NULL, xlabels = NULL, ylabels = NULL, + border = NA, add = FALSE, axes = TRUE, useRaster = FALSE, ...) { + xyzmat <- xyzmat.coords(x = x, y = y, z = zcol, + xlab = xlab, ylab = ylab, + xds = deparse(substitute(x)), yds = deparse(substitute(y))) + x <- xyzmat$x + y <- xyzmat$y + zcol <- xyzmat$z + xlab <- xyzmat$xlab + ylab <- xyzmat$ylab + if(is.null(xlab)) xlab <- NA + if(is.null(ylab)) ylab <- NA + nr <- nrow(zcol) + nc <- ncol(zcol) + if(min(zsize, na.rm = TRUE) < 0 || max(zsize, na.rm = TRUE) > 1) + stop ("expected 0 <= 'zsize' <= 1") + if (any(diff(x) <= 0) || any(diff(y) <= 0)) + stop("increasing 'x' and 'y' values expected") + if (length(x) == nr) { # "x" supplies midpoints + xmid <- x + if(nr > 1) { + dx <- 0.5 * diff(xmid) + xbreaks <- c(xmid[1] - dx[1], xmid[-length(xmid)] + dx, + xmid[length(xmid)] + dx[length(xmid) - 1]) + } else { + xbreaks <- c(xmid - 0.5, xmid + 0.5) + } + } else { # "x" supplies breakpoints + xbreaks <- x + xmid <- x[-1] - diff(x)/2 + } + if (length(y) == nc) { # "y" supplies midpoints + ymid <- y + if(nc > 1) { + dy <- 0.5 * diff(ymid) + ybreaks <- c(ymid[1] - dy[1], ymid[-length(ymid)] + dy, + ymid[length(ymid)] + dy[length(ymid) - 1]) + } else { + ybreaks <- c(ymid - 0.5, ymid + 0.5) + } + } else { # "y" supplies breakpoints + ybreaks <- y + ymid <- y[-1] - diff(y)/2 + } + xadj <- diff(xbreaks)[row(zcol)] * (1 - zsize) / 2 + yadj <- diff(ybreaks)[col(zcol)] * (1 - zsize) / 2 + xleft <- xbreaks[row(zcol)] + xadj + xright <- xbreaks[row(zcol) + 1] - xadj + ybottom <- ybreaks[col(zcol)] + yadj + ytop <- ybreaks[col(zcol) + 1] - yadj + if( !add ) { # draw frame, axes, labels + plot(range(xbreaks), range(ybreaks), + type = 'n', xaxs = 'i', yaxs = 'i', + xlab = xlab, ylab = ylab, axes = FALSE, ...) + if(axes) { + if(is.null(xlabels)) + axis(1, ...) + else if(length(xlabels) == 1 && is.logical(xlabels) && xlabels) + axis(1, at = xmid, labels = rownames(xyzmat$z), ...) + else + axis(1, at = xmid, labels = xlabels, ...) + if(is.null(ylabels)) + axis(2, ...) + else if(length(ylabels) == 1 && is.logical(ylabels) && ylabels) + axis(2, at = ymid, labels = colnames(xyzmat$z), ...) + else + axis(2, at = ymid, labels = ylabels, ...) + box(...) + } + } + canUseRaster <- (length(zsize) == 1) && (zsize == 1) && + diff(range(diff(xbreaks))) / diff(range(xbreaks)) < 0.01 && + diff(range(diff(ybreaks))) / diff(range(ybreaks)) < 0.01 + if(is.na(useRaster)) useRaster <- canUseRaster + if(useRaster) { # use rasterImage + if(!canUseRaster) stop ("cannot use useRaster = TRUE with non-uniform breakpoints") + flip <- function(x) t(x)[ncol(x):1, ] #rasterImage changes orientation + rasterImage(flip(zcol), xleft = min(xleft), ybottom = min(ybottom), + xright = max(xright), ytop = max(ytop), + interpolate = FALSE) + } else { # draw individual rectangles + rect(xleft = xleft, ybottom = ybottom, + xright = xright, ytop = ytop, + col = zcol, border = border ) + } +} + + +colorgram <- function(x = NULL, y = NULL, z = NULL, zsize = 1, + map, nz = 10, breaks = pretty, base = NA, colFn = jet, + key = hkey, key.args = list(), + xlab = NULL, ylab = NULL, zlab = NULL, + outlier = NULL, ...) { + xyzmat <- xyzmat.coords(x = x, y = y, z = z, + xlab = xlab, ylab = ylab, zlab = zlab, + xds = deparse(substitute(x)), yds = deparse(substitute(y)), + zds = deparse(substitute(z))) + if(missing(map)) { + map <- makecmap(xyzmat$z, n = nz, breaks = breaks, base = base, colFn = colFn) + } + zcol <- cmap(xyzmat$z, map = map, outlier = outlier) + cimage(x = xyzmat$x, y = xyzmat$y, zcol = zcol, zsize = zsize, + xlab = xyzmat$xlab, ylab = xyzmat$ylab, ... ) + if(is.function(key) || is.character(key)) + do.call(key, args = c(list(map = map, title = xyzmat$zlab), key.args)) + invisible(map) +} + + +squashgram <- function(x, y = NULL, z = NULL, FUN, + nx = 50, ny = nx, xlim = NULL, ylim = NULL, + xbreaks = NULL, ybreaks = NULL, + xlab = NULL, ylab = NULL, zlab = NULL, + shrink = 0, ...) { + xyz <- xyz.coords(x = x, y = y, z = z, + xlab = xlab, ylab = ylab, zlab = zlab) + if(is.null(xlab)) xlab <- xyz$xlab + if(is.null(xlab)) xlab <- deparse(substitute(x)) + if(is.null(ylab)) ylab <- xyz$ylab + if(is.null(ylab)) ylab <- deparse(substitute(y)) + if(is.null(zlab)) zlab <- xyz$zlab + if(is.null(zlab)) zlab <- deparse(substitute(z)) + zlab <- paste(deparse(substitute(FUN)), '(', zlab, ')', sep = '') + sq <- matapply(x = xyz$x, y = xyz$y, z = xyz$z, + FUN = FUN, nx = nx, ny = ny, + xlim = xlim, ylim = ylim, xbreaks = xbreaks, ybreaks = ybreaks) + if (shrink > 0) { + h <- hist2(x = xyz$x, y = xyz$y, + xbreaks = sq$x, ybreaks = sq$y, plot = FALSE) + zsize <- sqrt(pmin(h$z, shrink) / shrink) + } else { + zsize <- 1 + } + colorgram(sq, zsize = zsize, + xlab = xlab, ylab = ylab, zlab = zlab, ...) +} + + +hist2 <- function(x, y = NULL, + nx = 50, ny = nx, + xlim = NULL, ylim = NULL, + xbreaks = NULL, ybreaks = NULL, + plot = TRUE, + xlab = NULL, ylab = NULL, zlab = 'Counts', + colFn = heat, breaks = prettyInt, ...) { + xy <- xy.coords(x, y) + firstNonNull <- function(...) unlist(list(...))[1] + xlab <- firstNonNull(xlab, xy$xlab, deparse(substitute(x)), 'x') + ylab <- firstNonNull(ylab, xy$ylab, deparse(substitute(y)), 'y') + z <- rep(1, length(xy$x)) # dummy variable for tapply + h <- matapply(xy$x, xy$y, z, FUN = length, + nx = nx, ny = ny, xlim = xlim, ylim = ylim, + xbreaks = xbreaks, ybreaks = ybreaks) + h$xlab <- xlab + h$ylab <- ylab + h$zlab <- zlab + if(plot) { + colorgram(h, colFn = colFn, breaks = breaks, ...) + } + invisible(h) +} + + +dendromat <- function(x, mat, + labRow = rownames(mat), labCol = colnames(mat), + height = NA, gap = 0, matlabside = 2, border = NA, + cex.lab = par('cex.axis'), ...) { + stopifnot(matlabside %in% c(2, 4)) + if(is(x, 'hclust')) x <- as.dendrogram(x) + if(is.null(labRow)) labRow <- labels(x) + n <- attr(x, 'members') + if(nrow(mat) != n) stop("'nrow(mat)' must equal the number of leaves in 'x'") + ord <- order.dendrogram(x) + mat <- as.matrix(mat) + par(usr = c(0,1,0,1)) ## to ensure a consistent state after function finishes + op <- par(no.readonly = TRUE) + on.exit(par(op)) + on.exit(clip(0,1,0,1), add = TRUE) ## removes clipping region + mar <- par('mar') + if(is.na(height)) { + h.mat = par('csi') * ncol(mat) + h.lab = max(strwidth(labRow, 'inches')) * cex.lab + h.mar = 2 * par('csi') # set lower margin to 2 lines + h.tot = par('din')[2] + height = (h.mat + h.lab + h.mar) / h.tot + mar[1] <- 2 + (h.lab / par('csi')) + } + stopifnot(height < 1 && height > 0) + layout(matrix(1:2, ncol = 1), heights = c(1 - height, height)) + par(mar = c(gap, mar[2:4])) + plot(x, leaflab = 'none', ...) + usr <- par('usr') + par(mar = c(mar[1:2], 0, mar[4]), las = 2) + plot(0, 0, type = 'n', axes = FALSE, xlab = '', ylab = '') + par(usr = c(usr[1:2], 0.5, ncol(mat) + 0.5)) + cimage(mat[ord, , drop = FALSE], border = border, add = TRUE) + axis(matlabside, at = 1:ncol(mat), labels = labCol, + tick = FALSE, line = -0.5) + axis(1, at = 1:nrow(mat), labels = labRow[ord], + tick = FALSE, line = -0.5, cex.axis = cex.lab) +} + + +######### functions to draw color keys ########### + + +vkey <- function(map, title = NA, side = 2, stretch = 1.4, x, y, skip, wh) { + if(!missing(skip) && !missing(wh)) stop ("cannot specify both 'skip' and 'wh'") + opar <- par(xpd = NA) + on.exit(par(opar)) + n <- length(map$breaks) + dy <- strheight("A") + aspect <- diff(grconvertX(1:2, from ='inches')) / diff(grconvertY(1:2, from ='inches')) + dx <- dy * aspect + if(missing(wh)) { + if(missing(skip)) { # put as many labels as fit nicely + for (i in 1:min(n, 20)) { + if((n - 1) %% i == 0) { + step <- (n - 1) / i + wh.tmp <- seq(1, n, by = step) + if(strheight("A") * 1.2 < dy * step * stretch) wh <- wh.tmp + } + } + } else { + wh <- seq(1, n, by = skip) + } + } + labs <- format(map$breaks[wh]) + maxlabwidth <- max(strwidth(labs)) + if(missing(x)) { + x <- grconvertX(1, from = 'nfc') - (2 * dx) + if(side == 4) x <- x - maxlabwidth - dx + } else { + if(is.list(x)) { + y <- x$y + x <- x$x + } + } + if(missing(y)) y <- par('usr')[3] + dy + ybord <- y + ((0:(n-1)) * dy * stretch) + rect(x, ybord[-n], x + dx, ybord[-1], col = map$colors, border = NA) + if(side == 4) { + xtext <- x + dx + text(x = x, y = ybord[n] + (1.5 * dy), title, adj = c(0, 0)) + } + if(side == 2) { + xtext <- x + text(x = x + dx, y = ybord[n] + (1.5 * dy), title, adj = c(1, 0)) + } + text(x = xtext, y = ybord[wh], + labels = labs, pos = side) +} + + +hkey <- function(map, title = NA, side = 1, stretch = 1.4, x, y, skip, wh) { + if(!missing(skip) && !missing(wh)) stop ("cannot specify both 'skip' and 'wh'") + opar <- par(xpd = NA) + on.exit(par(opar)) + n <- length(map$breaks) + dy <- strheight("A") + aspect <- diff(grconvertX(1:2, from ='inches')) / diff(grconvertY(1:2, from ='inches')) + dx <- dy * aspect + labs <- format(map$breaks) + labwidth <- strwidth(labs) + if(missing(x)) { + x <- grconvertX(0, from = 'nfc') + dx + (0.5 * strwidth(format(map$breaks[1]))) + } else { + if(is.list(x)) { + y <- x$y + x <- x$x + } + } + if(missing(y)) y <- grconvertY(0, from = 'nfc') + (2 * dy) + xbord <- x + ((0:(n-1)) * dx * stretch) + if(missing(wh)) { + if(missing(skip)) { # put as many labels as fit nicely + for (i in 1:min(n, 20)) { + if((n - 1) %% i == 0) { + step <- (n - 1) / i + wh.tmp <- seq(1, n, by = step) + maxlabwidth <- max(strwidth(format(map$breaks[wh.tmp]))) + if(maxlabwidth + dx < dx * step * stretch) wh <- wh.tmp + } + } + } else { + wh <- seq(1, n, by = skip) + } + } + rect(xbord[-n], y, xbord[-1], y + dy, col = map$colors, border = NA) + if(side == 1) { + ytext <- y + text(x = x, y = y + (1.5 * dy), title, adj = c(0, 0)) + } + if(side == 3) { + ytext <- y + dy + text(x = x, y = y - (0.5 * dy), title, adj = c(0, 1)) + } + text(x = xbord[wh], y = ytext, + labels = format(map$breaks[wh]), pos = side) +} + + +######### file-writing function ########### + + +savemat <- function(x, filename, map = NULL, outlier = NULL, + dev = c('png', 'pdf', 'bmp', 'tiff', 'jpeg'), do.dev.off = TRUE, ...) { + dev <- match.arg(dev) + if(is.list(x)) x <- x$z + if(dev != 'pdf') { + do.call(dev, args = list(filename = filename, + width = nrow(x), height = ncol(x), + antialias = 'none', ...)) + } else if(dev == 'pdf') { + do.call(dev, args = list(file = filename, ...)) + } + par(mar = c(0, 0, 0, 0), ann = FALSE, + xaxt = 'n', yaxt = 'n', bty = 'n') + if(!is.null(map)) { + x <- cmap(x, map = map, outlier = outlier) + } + cimage(x, useRaster = TRUE) + if(do.dev.off) + dev.off() +} + + diff --git a/man/ColorPalettes.Rd b/man/ColorPalettes.Rd new file mode 100644 index 0000000..fa03153 --- /dev/null +++ b/man/ColorPalettes.Rd @@ -0,0 +1,76 @@ +\name{ColorPalettes} +\alias{greyscale} +\alias{grayscale} +\alias{rainbow2} +\alias{blueorange} +\alias{bluered} +\alias{jet} +\alias{heat} +\alias{coolheat} +\alias{darkbluered} +\title{ Bonus color palettes } +\description{ + Generate a vector of contiguous colors of a specified length. +} +\usage{ +rainbow2(n) +jet(n) +heat(n) +coolheat(n) +blueorange(n) +bluered(n) +darkbluered(n) +greyscale(n, start = 0.9, end = 0) +grayscale(n, start = 0.9, end = 0) +} +\arguments{ + \item{n}{ Number of colors to return. } + \item{start, end}{ Levels of gray (1 = white, 0 = black). } +} +\details{ + \code{rainbow2} is a variation of \code{\link[grDevices]{rainbow}}, in which the colors do not cycle completely around. Thus, \code{rainbow2} may be less ambiguous as a color scale. + + \code{jet} is similar to the Matlab color scheme of the same name and is taken from an example in \code{\link[grDevices]{colorRamp}}. + + \code{heat} is similar to \code{\link{heat.colors}}, but starts at black rather than red. + + \code{coolheat} is the diverging version of \code{heat}, running from cyan to black to yellow. + + \code{blueorange} and \code{bluered} range from blue to grey to orange (or red), and are intended to be used as diverging color scales. + + \code{darkbluered} ranges from dark blue to grey to dark red, and is intended to be used as a diverging color scale that emphasizes the magnitude more than the sign. + + \code{greyscale} or \code{grayscale} ranges from off-white to black. + +} +\value{ + A vector of RGB colors. +} +\seealso{ +Standard R palettes such as \code{\link[grDevices]{rainbow}}. + +Custom palettes can be generated with \code{\link[grDevices]{colorRamp}}. +} +\examples{ + +## Present the squash palettes along with the built-in R palettes +squash.palettes <- c('rainbow2', 'jet', 'grayscale', 'heat', 'coolheat', 'blueorange', 'bluered', 'darkbluered') +R.palettes <- c('rainbow', 'heat.colors', 'terrain.colors', 'topo.colors', 'cm.colors') + +plot(0:8, type = 'n', ann = FALSE, axes = FALSE) +for (i in 1:5) { + p <- R.palettes[i] + hkey(makecmap(c(0, 9), colFn = get(p)), + title = p, x = 2, y = i - 1) +} +for (i in 1:8) { + p <- squash.palettes[i] + hkey(makecmap(c(0, 9), colFn = get(p)), + title = p, x = 6, y = i - 1) +} +text(3, 8, 'R palettes', font = 2) +text(7, 8, 'squash palettes', font = 2) + +} +\keyword{ color } + diff --git a/man/cimage.Rd b/man/cimage.Rd new file mode 100644 index 0000000..038556d --- /dev/null +++ b/man/cimage.Rd @@ -0,0 +1,87 @@ +\name{cimage} +\alias{cimage} +\title{ Draw a matrix of colored rectangles } +\description{ + Draw a matrix of colored rectangles, possibly of varying sizes. +} +\usage{ +cimage(x = NULL, y = NULL, zcol = NULL, zsize = 1, + xlab = NULL, ylab = NULL, xlabels = NULL, ylabels = NULL, + border = NA, add = FALSE, axes = TRUE, useRaster = FALSE, ...) +} +\arguments{ + \item{x}{ Vector of rectangle midpoints or breakpoints along X-axis (corresponding to the columns of zcol). } + \item{y}{ Vector of rectangle midpoints or breakpoints along Y-axis (corresponding to the rows of zcol). } + \item{zcol}{ Matrix of colors for each rectangle, e.g. RGB values or integer indices. } + \item{zsize}{ Relative size for each rectangle, ranging from 0 to 1. Will be recycled if necessary. } + \item{xlab, ylab}{ Labels for the axes. } + \item{xlabels, ylabels}{ Categorical labels for rows/columns. } + \item{border}{ Color for rectangle borders. } + \item{add}{ Add to the current plot instead of creating a new one? } + \item{axes}{ Draw axes on the plot? } + \item{useRaster}{ TRUE = draw a true raster image (using \code{\link[graphics]{rasterImage}}). FALSE = draw a series of individual rectangles. } + \item{\dots}{ Further arguments passed to \code{\link{plot}}. } +} +\details{ + Data (\code{x}, \code{y}, and \code{zcol}) can be passed to this function in any format recognized by \code{\link{xyzmat.coords}}. + + This function is somewhat similar to the function \code{\link[graphics]{image}}, except that the colors are specified explicitly, and the size of each rectangle can be adjusted. + + If \code{xlabels} is \code{NULL} (the default), standard numeric axes are drawn on the X-axis. If \code{xlabels} is \code{TRUE}, the rownames of \code{zcol} are placed below each column. Otherwise, \code{xlabels} is taken as a vector of labels to be placed below each column. Likewise for \code{ylabels} and the Y-axis. + + Using \code{useRaster=TRUE} can reduce the file size for large matrices drawn to vector-based graphics output such as PDFs. However, the output may look strange with smaller matrices on graphics devices that do smoothing by default (such as PDF output viewed in Preview). +} +\value{ + None. +} +\note{ + Currently, this function will may not behave as expected if the \code{x} and/or \code{y} values are specified as midpoints and are not evenly spaced. +} +\seealso{ +\code{\link[graphics]{image}} and \code{\link[graphics]{rasterImage}} provide somewhat similar functionality. + +This function is called by \code{\link{colorgram}}, which accepts a numeric (rather than color) matrix as input. + +The package \pkg{pixmap} may be more suitable for plotting images that are not data-driven (e.g. external files). +} +\examples{ + + ## visualize nearly all built-in R colors + color.mat <- matrix(colors()[1:625], nrow = 25) + cimage(zcol = color.mat) + + ## an example using "zsize" + x <- y <- 1:10 + zcolor <- matrix( rainbow(100)[outer(x, y)], nrow = 10 ) + zsize <- matrix( runif(100), nrow = 10 ) + cimage(x, y, zcol = zcolor, zsize = zsize) + + ## another simple example + red <- green <- 0:255 + rg <- outer(red, green, rgb, blue = 1, maxColorValue = 255) + cimage(red, green, zcol = rg) + + ## same, but using useRaster (resulting in faster image generation, and smaller file size if saved as a PDF) + cimage(red, green, zcol = rg, useRaster = TRUE) + + ## an example with categorical axes + colormixer <- function(x, y) { + r <- (col2rgb(x) + col2rgb(y)) / 2 + rgb(as.data.frame(t(r)), maxColorValue = 255) + } + set.seed(123) + x <- sample(colors(), 15) + y <- sample(colors(), 10) + mix <- outer(x, y, colormixer) + op <- par(mar = c(8, 8, 2, 2), las = 2) + cimage(zcol = mix, xlabels = x, ylabels = y, xlab = NA, ylab = NA) + par(op) + + ## an example with nonuniform midpoints and breakpoints + rg2 <- rg[seq(1, 255, by = 62), seq(1, 255, by = 62)] + cimage(x = (1:5)^2, y = c(3, 5, 6, 9, 10, 11), zcol = rg2, + zsize = matrix(runif(25, min = 0.5), nrow = 5)) + +} +\keyword{ hplot } + diff --git a/man/cmap.Rd b/man/cmap.Rd new file mode 100644 index 0000000..a3dc852 --- /dev/null +++ b/man/cmap.Rd @@ -0,0 +1,50 @@ +\name{cmap} +\alias{cmap} +\title{ Apply a color map to numeric data } +\description{ + Map numeric (scalars, vectors, matrices) into colors, (optionally) using a specified color map. +} +\usage{ +cmap(x, map, outlier = NULL, ...) +} +\arguments{ + \item{x}{ Something numeric (vector, matrix). } + \item{map}{ The color map to use (as created by \code{\link{makecmap}}). If missing, a color map is created. } + \item{outlier}{ Color for values outside the map domain, or NULL to generate an error in case of such values (see Details).} + \item{\dots}{ Arguments passed to \code{\link{makecmap}}, if \code{map} is undefined. } +} +\details{ + + Values in \code{x} outside the domain of \code{map} cause either an error (if \code{outlier=NULL}) or a warning (otherwise). +} +\value{ + Something of the same size as \code{x}. May be character (RGB) or integer + (palettes) depending on the color map used. Dimensions and dimnames are preserved. +} +\seealso{ \code{\link{makecmap}}. Also, \code{\link[grDevices]{as.raster}} and \code{\link[lattice]{level.colors}} have similar functionality. } +\examples{ + x <- y <- 1:50 + mat1 <- outer(x, y) + + ## several ways of visualizing the matrix mat1: + plot(col(mat1), row(mat1), col = cmap(mat1), pch = 16) + + cimage(x, y, zcol = cmap(mat1)) + + colorgram(x = x, y = y, z = mat1) + + ## treatment of out-of-domain values + map <- makecmap(0:100, colFn = greyscale) + x <- y <- -10:10 + mat2 <- outer(x, y, "*") + + \dontrun{ + ## Values outside the domain of "map" generate an error... + plot(col(mat2), row(mat2), col = cmap(mat2, map), pch = 15, cex = 2) + + ## ... unless we specify "outlier", but this still generates a warning + plot(col(mat2), row(mat2), col = cmap(mat2, map, outlier = 'red'), pch = 15, cex = 2) + } + +} +\keyword{ color } diff --git a/man/colorgram.Rd b/man/colorgram.Rd new file mode 100644 index 0000000..a59537a --- /dev/null +++ b/man/colorgram.Rd @@ -0,0 +1,89 @@ +\name{colorgram} +\alias{colorgram} +\title{ Draw a colorgram (heatmap) of a matrix } +\description{ + Plot a visual representation of a numeric matrix using colors to indicate values. +} +\usage{ +colorgram(x = NULL, y = NULL, z = NULL, zsize = 1, + map, nz = 10, breaks = pretty, base = NA, colFn = jet, + key = hkey, key.args = list(), + xlab = NULL, ylab = NULL, zlab = NULL, + outlier = NULL, ...) +} +\arguments{ + \item{x, y}{ Locations of grid lines at which the values in z are measured. + These must be finite, non-missing and in (strictly) ascending order. (see Details below)} + \item{z}{ A numeric matrix containing the values to be visualized as colors (NAs are allowed). Note that x can be used instead of z for convenience. } + \item{zsize}{ A numeric matrix specifying the relative size of each rectangle. } + \item{map}{ A list, as generated by \code{\link{makecmap}}. If missing, a color map is generated automatically. } + \item{nz, breaks, base, colFn}{ Arguments passed to \code{\link{makecmap}}, if \code{map} is missing. } + \item{key}{ A function to draw a color key, such as \code{\link{hkey}} or \code{\link{vkey}}. } + \item{key.args}{ Arguments passed to the function given by \code{key}. } + \item{xlab, ylab}{ Labels for axes. } + \item{zlab}{ Label for the color key. } + \item{outlier}{ Color for values outside the \code{map} domain. + If NULL, values falling outside the map domain will generate an error. } + \item{\dots}{ Further arguments passed to \code{\link{cimage}}. } +} +\details{ + This function assigns colors to the elements of a matrix and plots it using \code{\link{cimage}}. + + Data can be passed to this function in any format recognized by \code{\link{xyzmat.coords}}. + + \code{colorgram} is somewhat similar to \code{\link[graphics]{image}}. However, \code{colorgram} adds the following functionality: 1. The value-to-color mapping can be specified (thus allowing unequal bin sizes). 2. A color key can be added, optionally. 3. A color can be specified for missing values. 4. The size of each grid rectangle can be adjusted to convey additional information. + + Two color key functions are provided in the beeswarm package: 1) \code{\link{hkey}} draws a horizontal key, in the lower-left corner by default. 2) \code{\link{vkey}}) draws a vertical key, in the lower-right corner by default. The latter usually looks better if the right-hand margin is increased. + +} +\value{ + Invisibly, \code{map}. +} +\seealso{ +If this is not quite what you are looking for, consider \code{\link[graphics]{image}}, \code{\link[graphics]{filled.contour}}, or \code{\link[lattice]{levelplot}}. Also \code{\link[plotrix]{color2D.matplot}} in the \pkg{plotrix} package. +} +\examples{ + + ## median Petal.Length as function of Sepal.Length and Sepal.Width + pl <- matapply( iris[,1:3], FUN = median, nx = 20, ny = 15 ) + + ## Draw a colorgram with the default horizontal color key + colorgram(pl, main = 'iris') + + ## ... or with the vertical color key + colorgram(pl, main = 'iris', key = vkey) + + ## ... add margin space to improve legibility + op <- par(mar = c(5,4,4,4)+0.1) + colorgram(pl, main = 'iris', key = vkey, + key.args = list(skip = 2), zlab = 'Petal\nlength') + par(op) + + ## Here is the example from \code{\link{persp}} + x <- seq(-10, 10, length= 30) + y <- x + f <- function(x,y) { r <- sqrt(x^2+y^2); 10 * sin(r)/(r) } + z <- outer(x, y, f) + colorgram(x, y, z) + + ## ... and with a slight fix to the key: + colorgram(x, y, z, key.args = list(wh = c(1, 4, 14))) + + ## We could also make more space for the key: + op <- par(mar = c(7,4,4,2)+0.1) + colorgram(x, y, z, key.args = list(stretch = 3)) + par(op) + + ## Here are some alternatives to colorgram + persp(x, y, z, theta = 30, phi = 30, expand = 0.5, col = "lightblue") + image(x, y, z) + contour(x, y, z) + + ## Use 'xlabels' and 'ylabels' to create categorical axes + colorgram(t(mtcars[,c(2,8:11)]), colFn = heat, + xlabels = TRUE, ylabels = TRUE, + xlab = NA, ylab = NA, zlab = 'Value', + main = 'Motor car specifications', las = 1) + +} +\keyword{ hplot } diff --git a/man/corrogram.Rd b/man/corrogram.Rd new file mode 100644 index 0000000..576b5e5 --- /dev/null +++ b/man/corrogram.Rd @@ -0,0 +1,22 @@ +\name{corrogram} +\alias{corrogram} +\title{ Draw a color-coded triangular matrix of pairwise correlations } +\description{ This figure is a color-coded, rotated triangular matrix indicating the correlation between every pair of items. } +\usage{ +corrogram(...) +} +\arguments{ + \item{\dots}{ Arguments passed to \code{\link{distogram}}. } +} +\details{ +This is a simple wrapper around \code{\link{distogram}}, with the color scale set by default to use \code{\link{blueorange}} with a range from -1 to +1. +} +\value{ +A color map (as generated by \code{\link{makecmap}}), invisibly. +} +\seealso{ \code{\link{distogram}} } +\examples{ + + corrogram(cor(swiss), title = 'Pearson correlation') +} +\keyword{ hplot } diff --git a/man/dendromat.Rd b/man/dendromat.Rd new file mode 100644 index 0000000..0753f5b --- /dev/null +++ b/man/dendromat.Rd @@ -0,0 +1,81 @@ +\name{dendromat} +\alias{dendromat} +\title{ Plot a dendrogram with a colorgram underneath } +\description{ +Plot a dendrogram with a colorgram underneath. The colorgram typically indicates characteristics about each element in the dendrogram. +} +\usage{ +dendromat(x, mat, + labRow = rownames(mat), labCol = colnames(mat), + height = NA, gap = 0, matlabside = 2, border = NA, + cex.lab = par('cex.axis'), ...) +} +\arguments{ + \item{x}{ An object of type \code{\link{hclust}} or \code{\link{dendrogram}}. } + \item{mat}{ A matrix or data frame of colors, with each row corresponding to an item in the dendrogram. } + \item{labRow}{ Labels of items, to be placed underneath the matrix. } + \item{labCol}{ Labels for characteristics, to be placed next to the matrix. } + \item{height}{ Fraction of the plot area to reserve for the color matrix. If NA, the spacing is set automatically. } + \item{gap}{ Extra space (in lines) to add between the dendrogram and the matrix. } + \item{matlabside}{ Which side of the matrix to put \code{labCol} (2 or 4). } + \item{border}{ Border color for the color matrix. } + \item{cex.lab}{ Relative text size for the item labels. } + \item{\dots}{ Further arguments passed to \code{\link{plot.dendrogram}}. } +} +\details{ +The order of \code{labRow} and the rows of \code{mat} should correspond to the input to \code{\link{hclust}} (or whatever function created \code{x}). This function reorders \code{mat} and \code{labRow} to match the dendrogram, using \code{\link{order.dendrogram}}. + +This function combines two plots using \code{\link{layout}}; therefore it is incompatible with other multiple-plot schemes (e.g. \code{par(mfrow)}). + +If \code{height == NA} (the default), the function tries to leave enough room for the item labels at the bottom, and enough room for the color matrix in the middle. The leftover plotting area on the top is used for the dendrogram. The lower margin setting (see \code{\link{par}}) is ignored. + +If \code{labRow} is set to \code{NULL}, or is equal to \code{NULL} because \code{mat} lacks rownames, then the item labels are taken from \code{x} instead. +} +\value{ none. } +\note{ +Currently, horizontal dendrograms are not supported. + +After \code{dendromat} is finished, the user coordinates are set to \code{c(0,1,0,1)}. +} +\seealso{ \code{\link{heatmap}} } +\examples{ + +## Motor Trend car road test data +mt.dend <- hclust(dist(mtcars[,1:7])) +mt.mat <- mtcars[,8:11] + +## A minimal dendromat +dendromat(mt.dend, mt.mat) + +## The same plot, but with a few enhancements +names(mt.mat) <- c('Straight', 'Manual', '# gears', '# carbs') +dendromat(mt.dend, mt.mat, gap = 0.5, border = 'gray', las = 2, + ylab = 'Euclidean distance', + main = 'mtcars, clustered by performance') +legend('topright', legend = 0:8, fill = 0:8) + +## US state data, with color keys +us.dend <- hclust(dist(scale(state.x77))) + +income <- state.x77[, 'Income'] +frost <- state.x77[, 'Frost'] +murder <- state.x77[, 'Murder'] + +income.cmap <- makecmap(income, n = 5, colFn = colorRampPalette(c('black', 'green'))) +frost.cmap <- makecmap(frost, n = 5, colFn = colorRampPalette(c('black', 'blue'))) +murder.cmap <- makecmap(murder, n = 5, colFn = colorRampPalette(c('black', 'red'))) + +us.mat <- data.frame(Frost = cmap(frost, frost.cmap), + Murder = cmap(murder, murder.cmap), + Income = cmap(income, income.cmap)) + +par(mar = c(5,4,4,3)+0.1) +dendromat(us.dend, us.mat, + ylab = 'Distance', main = 'US states') + +vkey(frost.cmap, 'Frost') +vkey(murder.cmap, 'Murder', y = 0.3) +vkey(income.cmap, 'Income', y = 0.7) + +} +\keyword{ hplot } diff --git a/man/diamond.Rd b/man/diamond.Rd new file mode 100644 index 0000000..c183ee5 --- /dev/null +++ b/man/diamond.Rd @@ -0,0 +1,24 @@ +\name{diamond} +\alias{diamond} +\title{ Draw diamonds } +\description{ Draw diamonds on the graphics device. } +\usage{ +diamond(x, y = NULL, radius, ...) +} +\arguments{ + \item{x, y}{ Position(s) of the centers of the diamonds. } + \item{radius}{ Distances from the center to the vertex. } + \item{\dots}{ Further arguments passed to \code{\link{polygon}} (e.g. \code{col}, \code{border}). } +} +\details{ +\code{x} and \code{y} can be passed to \code{diamond} in any form recognized by \code{\link{xy.coords}} (e.g. individual vectors, list, data frame, formula). + +Only \dQuote{square} (equilateral) diamonds are implemented here. } +\seealso{ \code{\link{rect}} } +\examples{ + plot(1:10) + diamond(1:10, rep(3, 10), radius = 0.4) + diamond(3, 8, 1, border = 3) + diamond(1:10, rep(5, 10), radius = seq(0.1, 1, length = 10), col = 1:10) +} +\keyword{ aplot } diff --git a/man/distogram.Rd b/man/distogram.Rd new file mode 100644 index 0000000..cda2854 --- /dev/null +++ b/man/distogram.Rd @@ -0,0 +1,32 @@ +\name{distogram} +\alias{distogram} +\title{ Draw a color-coded triangular distance matrix } +\description{ This figure is a color-coded, rotated triangular matrix indicating the distance between every pair of items. } +\usage{ +distogram(x, map, + n = 10, base = NA, colFn = heat, + key = TRUE, title = NA, ...) +} +\arguments{ + \item{x}{ A \code{\link{dist}} object, or a square numeric matrix. } + \item{map}{ A color map, as generated by \code{\link{makecmap}} (optional). } + \item{n, base, colFn}{ Arguments passed to \code{\link{makecmap}}, if \code{map} is omitted. } + \item{key}{ Add a color key? } + \item{title}{ Title for the color key. } + \item{\dots}{ Further arguments passed to \code{\link{trianglegram}}, (e.g. \code{labels}). } +} +\details{ + +} +\value{ The color map, invisibly. } +\seealso{ \code{\link{corrogram}} } +\examples{ + ## default + distogram(eurodist, title = 'Distance (km)') + + ## variations + map <- distogram(eurodist, key = FALSE, colFn = jet, right = TRUE) + vkey(map, title = 'Distance (km)', x = -8) + +} +\keyword{ hplot } diff --git a/man/hist2.Rd b/man/hist2.Rd new file mode 100644 index 0000000..97dd8ef --- /dev/null +++ b/man/hist2.Rd @@ -0,0 +1,61 @@ +\name{hist2} +\alias{hist2} +\title{ Bivariate histogram } +\description{ + Calculate data for a bivariate histogram and (optionally) plot it as a colorgram. +} +\usage{ +hist2(x, y = NULL, + nx = 50, ny = nx, + xlim = NULL, ylim = NULL, + xbreaks = NULL, ybreaks = NULL, + plot = TRUE, + xlab = NULL, ylab = NULL, zlab = "Counts", + colFn = heat, breaks = prettyInt, ...) +} +\arguments{ + \item{x, y}{ Numeric vectors. } + \item{nx, ny}{ Approximate number of intervals along x and y axes. } + \item{xlim, ylim}{ Limit the range of data points considered. } + \item{xbreaks, ybreaks}{ Breakpoints between bins along x and y axes. } + \item{plot}{ Plot the histogram? } + \item{xlab, ylab }{ Axis labels. } + \item{zlab}{ Label for the color key. } + \item{colFn, breaks}{ Color key parameters; see \code{\link{makecmap}}. } + \item{\dots}{ Further arguments passed to \code{\link{colorgram}}. } +} +\details{ + Data can be passed to \code{hist2} in any form recognized by \code{\link{xy.coords}} (e.g. individual vectors, list, data frame, formula). + +} +\value{ + Invisibly, a list with components: + \item{x }{Vector of breakpoints along the x-axis.} + \item{y }{Vector of breakpoints along the y-axis.} + \item{z }{Matrix of counts.} + \item{xlab }{A label for the x-axis.} + \item{ylab }{A label for the y-axis.} + \item{zlab }{A label for the color key.} +} +\seealso{ +\code{\link[graphics]{hist}}, for a standard (univariate) histogram. + +\code{\link[gplots]{hist2d}} in the \pkg{gplots} package for another implementation. + +The \pkg{hexbin} package, for a hexagonal implementation. +} +\examples{ + set.seed(123) + x <- rnorm(10000) + y <- rnorm(10000) + x + hist2(x, y) + + ## pseudo-log-scale color breaks: + hist2(x, y, breaks = prettyLog, key.args = list(stretch = 4)) + + ## log-scale color breaks; the old way using 'base' + ## (notice box removal to make space for the vertical color key) + hist2(x, y, base = 2, key = vkey, nz = 5, bty = 'l') + +} +\keyword{ hplot } diff --git a/man/hkey.Rd b/man/hkey.Rd new file mode 100644 index 0000000..c4392ae --- /dev/null +++ b/man/hkey.Rd @@ -0,0 +1,44 @@ +\name{hkey} +\alias{hkey} +\alias{vkey} +\title{ Add a color key to a plot } +\description{ Add a horizontal or vertical color key to a plot } +\usage{ +hkey(map, title = NA, side = 1, stretch = 1.4, x, y, skip, wh) +vkey(map, title = NA, side = 2, stretch = 1.4, x, y, skip, wh) +} +\arguments{ + \item{map}{ A list, as generated by \code{\link{makecmap}}. } + \item{title}{ Title for the key. } + \item{side}{ Where to place the labels. (1 or 3 for \code{hkey}, 2 or 4 for \code{vkey}) } + \item{stretch}{ Aspect ratio of the color rectangles. } + \item{x, y}{ Position of lower left corner of the color rectangles. If missing, the key will be placed automatically in the lower-left (\code{hkey}) or lower-right (\code{vkey}) corner of the figure region.} + \item{skip}{ Omit every \code{skip} labels (optional). } + \item{wh}{ Integer indices indicating which labels to include (optional). } +} +\details{ + +This functions tries to label as many breakpoints as possible, but if the labels would overlap a subset of labels is chosen automatically. If this doesn't look right, the subset of labels can be specified with either \code{skip} or \code{wh}. + +Clipping is turned off, so the key can be placed +anywhere in the figure region, including the margins. + +} +\examples{ + + attach(iris) + map <- makecmap(Petal.Length) + pl.color <- cmap(Petal.Length, map = map) + + plot(Sepal.Length, Sepal.Width, col = pl.color, pch = 16) + hkey(map, title = 'Petal length (hkey default)') + hkey(map, title = 'Another hkey', x = 3.8, y = 4.7, stretch = 3) + + ## looks bad with default margins + vkey(map, title = 'vkey default') + + vkey(map, title = 'Small vkey', x = 7.8, y = 4, stretch = 0.3) + +} +\keyword{ aplot } +\keyword{ color } diff --git a/man/makecmap.Rd b/man/makecmap.Rd new file mode 100644 index 0000000..0b20437 --- /dev/null +++ b/man/makecmap.Rd @@ -0,0 +1,60 @@ +\name{makecmap} +\alias{makecmap} +\title{ +Generate a color map from numeric values to colors + } +\description{ + Generate a color map from numeric values to a contiguous set of colors. + +} +\usage{ +makecmap(x, n = 10, breaks = pretty, + symm = FALSE, base = NA, + colFn = jet, col.na = NA, + right = FALSE, include.lowest = FALSE, ...) +} +\arguments{ + \item{x}{ A vector of numbers (only the finite range is used). } + \item{n}{ Approximate number of color levels desired. } + \item{breaks}{ A function to generate breakpoints, or the breakpoints themselves. } + \item{symm}{ Extend the mapping domain to be symmetric around zero? } + \item{base}{ Base for log scale, or NA to use a linear scale. } + \item{colFn}{ A function that generates contiguous colors. } + \item{col.na}{ Color to use for missing values. } + \item{right}{ Logical; if TRUE, the intervals will be closed on the right (and open on the left). } + \item{include.lowest}{ Logical, indicating if an \code{x[i]} equal to the lowest (or highest, for right = FALSE) \code{breaks} value should be included. } + \item{\dots}{ Further arguments to \code{breaks}. } +} +\details{ + The general point of this function is to generate a mapping that can be used in combination with \code{\link{cmap}} to represent numeric data with colors in a consistent way. + + \code{colFn} should be a function that returns a vector of colors of specified length, such as \code{\link{rainbow}}, \code{\link{greyscale}}. Custom functions of this type can be generated with \code{\link{colorRampPalette}}. + + The breakpoints can be specified explicitly, in which case \code{x} is ignored. Otherwise, the breakpoints are chosen to be nice, relatively round values (using \code{\link{pretty}}) covering the finite range of \code{x}. Other functions such as \code{\link{prettyInt}} might also yield pleasing results. However, if \code{diff(range(x)) == 0}, breakpoints are chosen to be \code{c(x, x + 1)} or \code{c(x - 1, x)} depending on \code{right}. + + If \code{symm} is TRUE, the map domain is extended such that it is symmetric around zero. This can be useful when using divergent color palettes to ensure that the zero point is a neutral color. + + If \code{base} is specified, the breakpoints are generated using log-transformed data. +} +\value{ +A list with the following components: + \item{breaks }{ Breakpoints (numeric vector).} + \item{colors }{ Colors (character or numeric vector). } + \item{base }{ (as supplied in arguments) } + \item{col.na }{ (as supplied in arguments) } + \item{right }{ (as supplied in arguments) } + \item{include.lowest }{ (as supplied in arguments) } +} +\seealso{ + \code{\link{cmap}} and \code{\link{colorgram}} use the mappings generated by this function. + + \code{\link{hkey}} plots a color key. +} +\examples{ + attach(iris) + map <- makecmap(Petal.Length) + myColors <- cmap(Petal.Length, map = map) + plot(Sepal.Length, Sepal.Width, col = myColors, pch = 16) + hkey(map, title = 'Petal.Length') +} +\keyword{ color } diff --git a/man/matapply.Rd b/man/matapply.Rd new file mode 100644 index 0000000..7f202ac --- /dev/null +++ b/man/matapply.Rd @@ -0,0 +1,68 @@ +\name{matapply} +\alias{matapply} +\title{ Apply a function over z coordinates, binned by their x, y coordinates} +\description{ + Divide the range of x and y into intervals, thus forming a matrix of bins, and apply an arbitrary function to the z values corresponding to each bin. +} +\usage{ +matapply(x, y = NULL, z = NULL, FUN, + nx = 50, ny = nx, + xlim = NULL, ylim = NULL, + xbreaks = NULL, ybreaks = NULL, + right = FALSE, include.lowest = TRUE, ...) +} +\arguments{ + \item{x, y, z}{ Numeric vectors, or possibly a matrix. } + \item{FUN}{ Function to summarize z values. } + \item{nx, ny}{ Approximate number of bins along x and y axis. } + \item{xlim, ylim}{ Limit the range of data points considered.} + \item{xbreaks, ybreaks}{ Breakpoints between bins along x and y axes. } + \item{right}{ Logical; if TRUE, the intervals will be closed on the right (and open on the left). } + \item{include.lowest}{ Logical, indicating if an \code{x[i]} equal to the lowest (or highest, for right = FALSE) \code{breaks} value should be included. } + \item{\dots}{ Further arguments to \code{FUN}. } +} +\details{ + \code{x}, \code{y} and \code{z} values can be passed to \code{squash} in any form recognized by \code{\link{xyz.coords}} (e.g. individual vectors, list, data frame, formula). + + Alternatively, data that is already in a matrix can be passed in any format recognized by \code{\link{xyzmat.coords}}. + + \code{FUN} should accept a numeric vector and return a single numeric value (e.g. \code{mean}, \code{median}, \code{min}, \code{max}, \code{sd}). + + If \code{xbreaks} is not specified, approximately \code{nx} breakpoints will be generated automatically to span the data; likewise for \code{ybreaks} and \code{ny}. + + The output can be visualized with \code{\link{colorgram}}, \code{\link[graphics]{image}}, etc. +} +\value{ + A list with components + \item{x }{Vector of breakpoints along the x-axis.} + \item{y }{Vector of breakpoints along the y-axis.} + \item{z }{Matrix of values representing the summary for each bin.} + \item{xlab }{A label for the x-axis.} + \item{ylab }{A label for the y-axis.} + \item{zlab }{A label for the z-axis.} +} +\note{ + The defaults of \code{right} and \code{include.lowest} are opposite the defaults used in \code{\link{cut}}. +} +\seealso{ +This function is essentially a souped-up version of \code{\link{tapply}}. + +\code{\link{squashgram}} has similar functionality but with graphical output. +} +\examples{ + ## earthquake depths as a function of longitude, latitude + attach(quakes) + quakedepth <- matapply(depth ~ long + lat, FUN = mean) + colorgram(quakedepth) + + ## iris petal length vs. sepal length and width + ipl <- matapply(iris[,1:3], FUN = median, nx = 20, ny = 15 ) + colorgram(ipl, main = 'iris') + + ## Example of matrix input; here used to downsample an image + colorgram(volcano, colFn = terrain.colors) + volcano2 <- matapply(volcano, FUN = mean, nx = 20) + colorgram(volcano2, colFn = terrain.colors) + +} +\keyword{ misc } diff --git a/man/prettyInt.Rd b/man/prettyInt.Rd new file mode 100644 index 0000000..deeed9b --- /dev/null +++ b/man/prettyInt.Rd @@ -0,0 +1,48 @@ +\name{prettyInt} +\alias{prettyInt} +\alias{prettyLog} +\title{ Pretty breakpoints } +\description{ Compute a sequence of around \code{n} values covering the range of \code{x}. + These functions are variations of the standard R function \code{\link{pretty}}. } +\usage{ +prettyInt(x, n = 5, ...) +prettyLog(x, n = 5, small = NA, logrange = c(-100, 100)) +} +\arguments{ + \item{x}{ Numeric vector. } + \item{n}{ Approximate number of values to return. } + \item{small}{ No. } + \item{logrange}{ Log (base 10) of the range of values to consider as possible breakpoints. } + \item{\dots}{ Further arguments passed to \code{\link{pretty}}. } +} +\details{ +\code{prettyInt} returns integer values, even if this forces the number of values returned to be much lower than the requested number \code{n}. + +\code{prettyLog} returns values that are approximately evenly spaced on a log scale, such as (1, 3, 10, 30, ...) or (1, 2, 5, 10, 20, 50, ...) or (1, 10, 100, ...). +Negative or zero values in \code{x} are accomodated by series such as (-100, -10, -1, 0, 1, 10, 100, ...). Setting the parameter \code{small} to a non-\code{NA} value will ignore \code{x} values below \code{abs(small)}. + +} +\value{ A numeric vector. } +\seealso{ \code{\link{pretty}} } +\examples{ +## +x1 <- 1:3 +pretty(x1) +prettyInt(x1) +prettyLog(x1) + +## +x2 <- pi ^ (1:8) +range(x2) +pretty(x2) +prettyLog(x2) +prettyLog(x2, n = 10) + +## +x3 <- c(-x2, x2) +pretty(x3) +prettyLog(x3) +prettyLog(x3, small = 100) + +} +\keyword{ dplot } diff --git a/man/savemat.Rd b/man/savemat.Rd new file mode 100644 index 0000000..b7ab038 --- /dev/null +++ b/man/savemat.Rd @@ -0,0 +1,42 @@ +\name{savemat} +\alias{savemat} +\title{Save a matrix as a raster image file} +\description{Save a matrix as a PNG, TIFF, BMP, JPEG, or PDF image file, such that each pixel corresponds to exactly one element +of the matrix. } +\usage{ +savemat(x, filename, map = NULL, outlier = NULL, + dev = c('png', 'pdf', 'bmp', 'tiff', 'jpeg'), + do.dev.off = TRUE, ...) +} +\arguments{ + \item{x}{ A matrix } + \item{filename}{ Filename } + \item{map}{ (Optional) a list, as generated by \code{\link{makecmap}}. } + \item{outlier}{ (Optional) A color for outliers, if \code{map} is specified. } + \item{dev}{ Which graphics device to use. } + \item{\dots}{ Further arguments passed to the graphics device; see \code{\link{png}} or \code{\link{pdf}}. } + \item{do.dev.off}{ Close graphics device when finished? } + } +\details{ +This function is a relatively simple wrapper around the usual graphics device with the same name as \code{dev}. The idea is to provide an easy way of creating an image file from a matrix, without axes, plotting frame, labels, etc. + +For all choices of \code{dev} except \code{"pdf"}, the output image dimensions are set to match the matrix size, such that each pixel corresponds to an element of the matrix. + +If \code{map} is \code{NULL} (the default), the matrix is interpreted as a matrix of colors. + +If \code{map} is specified, it is used to translate +the numeric matrix \code{x} into a matrix of colors, +using \code{\link{cmap}}. +} +\value{ None. } +\seealso{ \code{\link{cimage}} for drawing a matrix on the screen. } +\examples{ +\dontrun{ + big.color.matrix <- matrix(rep(colors()[1:625], 16), nrow = 100) + + ## save as a PNG + savemat(big.color.matrix, file = 'test.png') + +} +} +\keyword{ misc } diff --git a/man/squashgram.Rd b/man/squashgram.Rd new file mode 100644 index 0000000..12ea08c --- /dev/null +++ b/man/squashgram.Rd @@ -0,0 +1,63 @@ +\name{squashgram} +\alias{squashgram} +\title{ Visualize a function of z coordinates, binned by x, y coordinates} +\description{ + This is a convenience function combining \code{matapply} and \code{colorgram}. 3-dimensional data is summarized in 2-dimensional bins and represented as a color matrix. Optionally, the number of observations in each bin is indicated by relative size of the matrix elements. +} +\usage{ +squashgram(x, y = NULL, z = NULL, FUN, + nx = 50, ny = nx, xlim = NULL, ylim = NULL, + xbreaks = NULL, ybreaks = NULL, + xlab = NULL, ylab = NULL, zlab = NULL, + shrink = 0, ...) +} +\arguments{ + \item{x, y, z}{ Numeric vectors; see Details. } + \item{FUN}{ Function to summarize z values. } + \item{nx, ny}{ Approximate number of bins along x and y axis. } + \item{xlim, ylim}{ Limit the range of data points considered. } + \item{xbreaks, ybreaks}{ Breakpoints between bins along x and y axes. } + \item{xlab, ylab }{ Axis labels. } + \item{zlab}{ Label for color key. } + \item{shrink}{ Rectangle shrinkage cutoff. } + \item{\dots}{ Further arguments passed to \code{\link{colorgram}}. } +} +\details{ + This function may be useful for visualizing the dependence of a variable (\code{z}) on two other variables (\code{x} and \code{y}). + + \code{x}, \code{y} and \code{z} values can be passed to \code{squash} in any form recognized by \code{\link{xyz.coords}} (e.g. individual vectors, list, data frame, formula). + + This function calls \code{\link{matapply}} and plots the result along with a color key. + + If non-zero, the \code{shrink} parameter reduces the size of rectangles for + the bins in which the number of samples is smaller than \code{shrink}. This may be useful to reduce the visual impact of less reliable observations. +} +\value{ + None. +} +\seealso{ The lower-level functions \code{\link{matapply}} and \code{\link{colorgram}}. } +\examples{ + ## earthquake depths in Fiji + attach(quakes) + squashgram(depth ~ long + lat, FUN = mean) + + ## iris measurements + attach(iris) + squashgram(Sepal.Length, Sepal.Width, Petal.Length, + FUN = median, nx = 20, ny = 15) + + ## Here indicate sample size by size of rectangles + squashgram(iris[,1:3], FUN = median, + nx = 20, ny = 15, shrink = 5) + + ## What is the trend in my noisy 3-dimensional data? + set.seed(123) + x <- rnorm(10000) + y <- rnorm(10000) + z <- rnorm(10000) + cos(x) + abs(y / 4) + squashgram(x, y, z, median, colFn = bluered, shrink = 5) + +} +\keyword{ hplot } + + diff --git a/man/trianglegram.Rd b/man/trianglegram.Rd new file mode 100644 index 0000000..a461675 --- /dev/null +++ b/man/trianglegram.Rd @@ -0,0 +1,32 @@ +\name{trianglegram} +\alias{trianglegram} +\title{ Draw a color-coded triangular matrix } +\description{ This function is called by \code{\link{distogram}}, and probably isn't very useful by itself. } +\usage{ +trianglegram(x, labels = rownames(x), + lower = TRUE, diag = FALSE, right = FALSE, + add = FALSE, xpos = 0, ypos = 0, xlim, ylim, ...) +} +\arguments{ + \item{x}{ A square matrix containing color values. } + \item{labels}{ Labels. } + \item{lower}{ If TRUE, use \code{\link{lower.tri}}, else use \code{\link{upper.tri}}. } + \item{diag}{ Include the diagonal elements of \code{x}? } + \item{right}{ Should triangle point to the right or left? } + \item{add}{ Add to an existing plot? } + \item{xpos, ypos}{ Location of bottom point of the triangle. } + \item{xlim, ylim}{ Plotting limits. } + \item{\dots}{ Further arguments passed to \code{\link{plot}}. } +} +\details{ +} +\value{ none. } +\seealso{ \code{\link{distogram}}, \code{\link{corrogram}} } +\examples{ + m <- matrix(jet(40), nrow = 20, ncol = 20) + trianglegram(m) + + ## just for fun + trianglegram(m, labels = NA, right = TRUE, add = TRUE, xpos = 1) +} +\keyword{ aplot } diff --git a/man/xyzmat.coords.Rd b/man/xyzmat.coords.Rd new file mode 100644 index 0000000..4d7c01e --- /dev/null +++ b/man/xyzmat.coords.Rd @@ -0,0 +1,42 @@ +\name{xyzmat.coords} +\alias{xyzmat.coords} +\title{Extract (x, y, z) coordinates, where z is a matrix} +\description{ +Extract (x, y, z) plotting coordinates, where z is a matrix. +} +\usage{ +xyzmat.coords(x = NULL, y = NULL, z = NULL, + xlab = NULL, ylab = NULL, zlab = NULL, + xds = NULL, yds = NULL, zds = NULL) +} +\arguments{ + \item{x, y}{ Numeric vectors. } + \item{z}{ A matrix } + \item{xlab, ylab, zlab}{ Labels } + \item{xds, yds, zds}{ Results from \code{deparse(substitute(x))} (etc.); see below.} +} +\details{ +This function is similar to \code{\link{xyz.coords}}, except that this function accepts a matrix for \code{z}. + +If \code{x} is the same length as \code{nrow(z)}, \code{x} will be taken as the points at which the \code{z} values were sampled. If \code{x} is the length of \code{nrow(z) + 1}, \code{x} is taken as the breakpoints between bins. If \code{x} is missing, the matrix indices (\code{1:nrow(z)}) will be used. Similarly for \code{y} and the columns of \code{z}. + +For convenience, the matrix can supplied as the \code{x} argument. Or, \code{x} can be a list with elements including \{x, y, z, xlab, ylab, zlab\}. + +When this function is used inside a higher-level plotting function, the arguments \code{xds}, \code{yds}, and \code{zds} should be set to \code{deparse(substitute(x))} (etc.) so that the function can generate informative default axis labels. For example, see the code for \code{\link{colorgram}}. +} +\value{ +A list with the following components: + \item{x }{ X coordinates } + \item{y }{ Y coordinates } + \item{z }{ Z matrix } + \item{xlab }{ Label for X axis } + \item{ylab }{ Label for Y axis } + \item{zlab }{ Label for Z axis } +} +\examples{ + ## + str(volcano) + volcano.xyzmat <- xyzmat.coords(volcano) + str(volcano.xyzmat) +} +\keyword{ manip } diff --git a/man/xyzmat2xyz.Rd b/man/xyzmat2xyz.Rd new file mode 100644 index 0000000..8800ff7 --- /dev/null +++ b/man/xyzmat2xyz.Rd @@ -0,0 +1,27 @@ +\name{xyzmat2xyz} +\alias{xyzmat2xyz} +\title{Convert (x, y, zmat) coordinates to (x, y, z) coordinates} +\description{ +Convert a matrix of Z coordinates into (x, y, z) triples. +} +\usage{ +xyzmat2xyz(...) +} +\arguments{ + \item{\dots}{ Arguments passed to \code{\link{xyzmat.coords}} } +} +\details{ +The input is based on \code{\link{xyzmat.coords}}. + +The output is as returned by \code{\link{xyz.coords}} +} +\value{ +A list; see \code{\link{xyz.coords}}. +} +\examples{ + ## + str(volcano) + volcano.xyz <- xyzmat2xyz(volcano) + str(volcano.xyz) +} +\keyword{ manip }