diff --git a/NAMESPACE b/NAMESPACE index 796c7fdb..13c971c4 100755 --- a/NAMESPACE +++ b/NAMESPACE @@ -14,6 +14,7 @@ export("chordDiagramFromMatrix") export("circlize") export("circos.arrow") export("circos.axis") +export("circos.boxplot") export("circos.clear") export("circos.dendrogram") export("circos.genomicAxis") @@ -31,6 +32,8 @@ export("circos.genomicRect") export("circos.genomicText") export("circos.genomicTrack") export("circos.genomicTrackPlotRegion") +export("circos.heatmap") +export("circos.heatmap.initialize") export("circos.info") export("circos.initialize") export("circos.initializeWithIdeogram") @@ -53,6 +56,7 @@ export("circos.trackText") export("circos.triangle") export("circos.update") export("circos.updatePlotRegion") +export("circos.violin") export("circos.xaxis") export("circos.yaxis") export("col2value") @@ -109,6 +113,7 @@ importFrom("grDevices", rgb) importFrom("grid", grid.pretty) importFrom("methods", as) importFrom("shape", Arrowhead) +importFrom("stats", "as.dendrogram", "dist", "hclust", "order.dendrogram") importFrom("stats", rnorm) importFrom("stats", runif) importFrom("utils", download.file) diff --git a/NEWS b/NEWS index d031ebad..b6dbb339 100755 --- a/NEWS +++ b/NEWS @@ -8,6 +8,9 @@ Changes in version 0.4.10 * `get.cell.meta.data()`: add `cell.width` and `cell.height` arguments. * `circos.genomicTrackPlotRegion()`: when input is a data frame list and column.index is a vector, reduce the one-column data frame to a vector. +* add `add.track.meta.data()` and `add.sector.meta.data()` too add user-defined cell meta data. +* add `circos.heatmap()` to draw multi-track heatmaps. +* add `circos.boxplot()` and `circos.violin()`. Changes in version 0.4.9 ----------------------------------------------------------------------- diff --git a/R/circos.heatmap.R b/R/circos.heatmap.R new file mode 100644 index 00000000..5c173406 --- /dev/null +++ b/R/circos.heatmap.R @@ -0,0 +1,323 @@ + +# returns a list of named data frames +circos.heatmap.format.input = function(x, split) { + if(is.atomic(x) && !is.matrix(x)) x = matrix(x, ncol = 1) + if(is.data.frame(x)) x = as.matrix(x) + + subset_list = NULL + if(is.matrix(x)) { + if(is.null(split)) { + if(is.circos.heatmap.cached()) { + # qqcat("use the cached split\n") + env = circos.par("__tempenv__") + split = env$circos.heatmap.split + } + } + if(is.null(split)) { + mat_list = list(mat = x) + subset_list = list(mat = 1:nrow(x)) + } else { + mat_list = lapply(split(seq_len(nrow(x)), split), function(ind) x[ind, , drop = FALSE]) + subset_list = split(seq_len(nrow(x)), split) + } + } else { + mat_list = x + } + + n = length(mat_list) + if(is.null(names(mat_list))) { + names(mat_list) = paste0("mat", 1:n) + } + + attr(mat_list, "subset_list") = subset_list + mat_list +} + +is.circos.heatmap.cached = function() { + env = circos.par("__tempenv__") + identical(env$circos.heatmap.initialized, TRUE) +} + +# == title +# Initialize circular heatmaps +# +# == param +# -x A matrix or a list of matrices. If the value is a vector, it is converted +# into a one-column matrix. +# -split A categorical variable. If the ``x`` is a matrix, it splits the matrix into a list of matrices. +# -cluster whether to apply clustering on rows. +# -clustering.method Clustering method, pass to `stats::hclust`. +# -distance.method Distance method, pass to `stats::dist`. +# +circos.heatmap.initialize = function(x, split = NULL, cluster = TRUE, + clustering.method = "complete", distance.method = "euclidean") { + + mat_list = circos.heatmap.format.input(x, split) + n = length(mat_list) + subset_list = attr(mat_list, "subset_list") + + # qqcat("initialize the circular plot with @{n} matrices.\n") + circos.initialize(names(mat_list), xlim = cbind(rep(0, n), sapply(mat_list, nrow))) + + if(is.character(mat_list[[1]])) cluster = FALSE + + env = circos.par("__tempenv__") + if(cluster) { + # qqcat("perform clustering.\n") + dend_list = lapply(mat_list, function(m) as.dendrogram(hclust(dist(m, method = distance.method), method = clustering.method))) + for(se in get.all.sector.index()) { + add.sector.meta.data("row_dend", dend_list[[se]], sector.index = se) + add.sector.meta.data("dend", dend_list[[se]], sector.index = se) + add.sector.meta.data("row_order", order.dendrogram(dend_list[[se]]), sector.index = se) + add.sector.meta.data("order", order.dendrogram(dend_list[[se]]), sector.index = se) + if(!is.null(subset_list)) { + add.sector.meta.data("subset", subset_list[[se]], sector.index = se) + } + } + env$circos.heatmap.cluster = TRUE + } else { + # qqcat("use the natural order.\n") + for(se in get.all.sector.index()) { + add.sector.meta.data("row_order", 1:nrow(mat_list[[se]]), sector.index = se) + add.sector.meta.data("order", 1:nrow(mat_list[[se]]), sector.index = se) + if(!is.null(subset_list)) { + add.sector.meta.data("subset", subset_list[[se]], sector.index = se) + } + } + env$circos.heatmap.cluster = FALSE + } + env$circos.heatmap.split = split + env$circos.heatmap.initialized = TRUE + +} + +# e.g. to check number of rows, split varaible, ... +circos.heatmap.validate = function(mat_list) { + + # assume the heatmap is already initialized + env = circos.par("__tempenv__") + order_list = lapply(env$sector.meta.data, function(x) { + x$row_order + }) + + if(!identical(unname(sapply(mat_list, nrow)), unname(sapply(order_list, length)))) { + stop_wrap("The numbers of total rows and in each group are different from the cached values. Maybe you should 1. provide the matrix with the same number of rows as the previous ones, 2. don't set `split` because only the cached one is used, or 3. apply `circos.clear()` if you are making a new plot.") + } +} + +# == title +# Make circular heatmaps +# +# == param +# -x A matrix or a list of matrices. If the value is a vector, it is converted +# into a one-column matrix. +# -split A categorical variable. If the ``x`` is a matrix, it splits the matrix into a list of matrices. +# -col If the values in the matrices are continuous, the color should be a color mapping generated by +# `colorRamp2`. If the values are characters, the color should be a named color vector. +# -na.col Color for ``NA`` values. +# -ignore_white Whether to draw the white color? +# -default.par By default `circos.par` is set as ``cell.padding = c(0, 0, 0, 0), track.margin = c(0.02, 0), gap.degree = 2``. +# Set this value to ``FALSE`` to use your own `circos.par`. +# -cluster whether to apply clustering on rows. +# -clustering.method Clustering method, pass to `stats::hclust`. +# -distance.method Distance method, pass to `stats::dist`. +# -dend.side Side of the dendrograms relative to the heatmap track. +# -dend.track.height Track height of the dendrograms. +# -rownames.side Side of the row names relative to the heatmap track. +# -rownames.cex Cex of row names. +# -rownames.font Font of row names. +# -... Pass to `circos.track` which draws the heatmap track. +# +# == example +# set.seed(123) +# mat = matrix(rnorm(1000), nr = 100) +# rownames(mat) = paste0("R", 1:100) +# split = rep(letters[1:5], times = 10) +# +# circos.clear() +# circos.heatmap(mat, split = split, +# col = colorRamp2(c(-2, 0, 2), c("blue", "white", "red"))) +# +# row_mean = rowMeans(mat) +# circos.track(ylim = range(row_mean), panel.fun = function(x, y) { +# y = row_mean[split == CELL_META$sector.index] +# y = y[CELL_META$row_order] +# circos.lines(CELL_META$cell.xlim, c(0, 0), lty = 2, col = "grey") +# circos.points(seq_along(y) - 0.5, y, col = ifelse(y > 0, "red", "blue")) +# }, cell.padding = c(0.02, 0, 0.02, 0)) +# circos.clear() +# +# circos.clear() +# circos.heatmap.initialize(mat, split = split) +# row_mean = rowMeans(mat) +# circos.track(ylim = range(row_mean), panel.fun = function(x, y) { +# y = row_mean[split == CELL_META$sector.index] +# y = y[CELL_META$row_order] +# circos.lines(CELL_META$cell.xlim, c(0, 0), lty = 2, col = "grey") +# circos.points(seq_along(y) - 0.5, y, col = ifelse(y > 0, "red", "blue")) +# }, cell.padding = c(0.02, 0, 0.02, 0)) +# circos.heatmap(mat, col = colorRamp2(c(-2, 0, 2), c("blue", "white", "red"))) +# circos.clear() +# +circos.heatmap = function(x, split = NULL, col, na.col = "grey", + ignore_white = TRUE, default.par = TRUE, + cluster = TRUE, clustering.method = "complete", distance.method = "euclidean", + dend.side = c("none", "outside", "inside"), dend.track.height = 0.1, + rownames.side = c("none", "outside", "inside"), + rownames.cex = 0.5, + rownames.font = par("font"), + ...) { + + mat_list = circos.heatmap.format.input(x, split) + + if(is.circos.initialized()) { + circos.heatmap.validate(mat_list) + } else { + if(default.par) { + circos.par(cell.padding = c(0, 0, 0, 0), track.margin = c(0.02, 0), gap.degree = 2) + } + circos.heatmap.initialize(x, split = split, cluster = cluster, + clustering.method = clustering.method, distance.method = distance.method) + } + + env = circos.par("__tempenv__") + # qqcat("making the heatmap\n") + + dend.side = match.arg(dend.side) + rownames.side = match.arg(rownames.side) + if(dend.side == rownames.side && dend.side %in% c("inside", "outside")) { + stop_wrap("dendrograms and row names cannot be on the same side.") + } + + if(!env$circos.heatmap.cluster) { + dend.side = "none" + } + + if(dend.side == "outside") { + dend_list = lapply(env$sector.meta.data, function(x) { + x$row_dend + }) + max_height = max(sapply(dend_list, function(x) attr(x, "height"))) + circos.track(ylim = c(0, max_height), bg.border = NA, track.height = dend.track.height, + panel.fun = function(x, y) { + sector.numeric.index = get.cell.meta.data("sector.numeric.index") + dend = dend_list[[sector.numeric.index]] + circos.dendrogram(dend, max_height = max_height, facing = "inside") + }) + } + + if(rownames.side == "outside") { + rownames_list = lapply(mat_list, rownames) + if(!all(sapply(rownames_list, is.null))) { + rownames_track_height = max(strwidth(unlist(rownames_list), cex = rownames.cex, font = rownames.font)) + circos.track(ylim = c(0, 1), bg.border = NA, track.height = rownames_track_height, + panel.fun = function(x, y) { + sector.numeric.index = CELL_META$sector.numeric.index + m = mat_list[[sector.numeric.index]] + od = CELL_META$row_order + nr = nrow(m) + + if(!is.null(rownames(m))) { + circos.text(1:nr - 0.5, rep(0, nr), rownames(m)[od], cex = rownames.cex, + font = rownames.font, facing = "clockwise", niceFacing = TRUE, adj = c(0, 0.5)) + } + + }) + } + } + + nr = nrow(mat_list[[1]]) + nc = ncol(mat_list[[1]]) + + if(missing(col)) { + stop_wrap("You should provide user-defined colors. If the values are continuous in the matrix, please set a color mapping function generated by `colorRamp2()`. If the values are characters, please set a named color vector.") + } + + if(is.function(col)) { + col_fun = col + } else { + col_fun = function(x) { + attr = attributes(x) + v = col[x] + v[is.na(v)] = na.col + attributes(v) = attr + v + } + } + + circos.track(ylim = c(0, nc), bg.border = NA, panel.fun = function(x, y) { + + sector.numeric.index = CELL_META$sector.numeric.index + m = mat_list[[sector.numeric.index]] + od = CELL_META$row_order + + m2 = m[od, , drop = FALSE] + col_mat = col_fun(m2) + if(!grepl("#\\w\\w\\w\\w\\w\\w", col_mat[1])) { + col_mat_attr = attributes(col_mat) + col_mat = as.vector(col_mat) + col_rgb = col2rgb(col_mat, alpha = TRUE) + col_mat = rgb(col_rgb[1, ], col_rgb[2, ], col_rgb[3, ], alpha = col_rgb[4, ], maxColorValue = 255) + attributes(col_mat) = col_mat_attr + } + nr = nrow(m2) + nc = ncol(m2) + + for(i in 1:nc) { + if(ignore_white) { + l = grepl("#FFFFFF", col_mat[, i]) # white colors + if(all(l)) { + # no nothing + } else { + # qqcat("@{sum(l)} white rectangles are not drawn.\n") + circos.rect( + (1:nr - 1)[!l], + (rep(nc - i, nr))[!l], + (1:nr)[!l], + (rep(nc - i + 1, nr))[!l], + border = col_mat[, i][!l], + col = col_mat[, i][!l]) + } + } else { + circos.rect(1:nr - 1, rep(nc - i, nr), + 1:nr, rep(nc - i + 1, nr), + border = col_mat[, i], col = col_mat[, i]) + } + } + + }, ...) + + + if(dend.side == "inside") { + dend_list = lapply(env$sector.meta.data, function(x) { + x$row_dend + }) + max_height = max(sapply(dend_list, function(x) attr(x, "height"))) + circos.track(ylim = c(0, max_height), bg.border = NA, track.height = dend.track.height, + panel.fun = function(x, y) { + sector.numeric.index = get.cell.meta.data("sector.numeric.index") + dend = dend_list[[sector.numeric.index]] + circos.dendrogram(dend, max_height = max_height, facing = "outside") + }) + } + + if(rownames.side == "inside") { + rownames_list = lapply(mat_list, rownames) + if(!all(sapply(rownames_list, is.null))) { + rownames_track_height = max(strwidth(unlist(rownames_list), cex = rownames.cex, font = rownames.font)) + circos.track(ylim = c(0, 1), bg.border = NA, track.height = rownames_track_height, + panel.fun = function(x, y) { + sector.numeric.index = CELL_META$sector.numeric.index + m = mat_list[[sector.numeric.index]] + od = CELL_META$row_order + nr = nrow(m) + + if(!is.null(rownames(m))) { + circos.text(1:nr - 0.5, rep(1, nr), rownames(m)[od], cex = rownames.cex, + font = rownames.font, facing = "clockwise", niceFacing = TRUE, adj = c(1, 0.5)) + } + + }) + } + } +} diff --git a/R/global.R b/R/global.R index 46a6e987..66072d33 100755 --- a/R/global.R +++ b/R/global.R @@ -168,6 +168,10 @@ circos.par = setGlobalOptions( '__omar__' = list( # is par("mar") the default value? .value = FALSE, .private = TRUE, + .visible = FALSE), + '__tempenv__' = list( + .value = new.env(parent = emptyenv()), + .private = TRUE, .visible = FALSE) ) @@ -438,9 +442,16 @@ circos.clear = function() { circos.par(RESET = TRUE) circos.par("__tempdir__" = tmpdir) + empty_env(circos.par("__tempenv__")) + return(invisible(NULL)) } +empty_env = function(env) { + obj = ls(envir = env, all.names = TRUE) + if(length(obj)) rm(list = obj, envir = env) +} + # == title # Get index for all sectors # @@ -812,11 +823,42 @@ get.cell.meta.data = function(name, sector.index = get.current.sector.index(), } else if(name == "track.height") { return(current.cell.data$track.height) } else { - stop_wrap("Wrong cell meta name.") + env = circos.par("__tempenv__") + if(!is.null(env$track.meta.data)) { + track.index = as.character(track.index) + if(!is.null(env$track.meta.data[[track.index]])) { + if(name %in% names(env$track.meta.data[[track.index]])) { + return(env$track.meta.data[[track.index]][[name]]) + } + } + } + if(!is.null(env$sector.meta.data)) { + if(!is.null(env$sector.meta.data[[sector.index]])) { + if(name %in% names(env$sector.meta.data[[sector.index]])) { + return(env$sector.meta.data[[sector.index]][[name]]) + } + } + } } + return(NULL) } +add.track.meta.data = function(name, value, track.index = get.current.track.index()) { + env = circos.par("__tempenv__") + if(is.null(env$track.meta.data)) env$track.meta.data = list() + track.index = as.character(track.index) + if(is.null(env$track.meta.data[[track.index]])) env$track.meta.data[[track.index]] = list() + env$track.meta.data[[track.index]][[name]] = value +} + +add.sector.meta.data = function(name, value, sector.index = get.current.sector.index()) { + env = circos.par("__tempenv__") + if(is.null(env$sector.meta.data)) env$sector.meta.data = list() + if(is.null(env$sector.meta.data[[sector.index]])) env$sector.meta.data[[sector.index]] = list() + env$sector.meta.data[[sector.index]][[name]] = value +} + # == title (variable:CELL_META) # Easy way to get meta data in the current cell # @@ -848,10 +890,32 @@ class(CELL_META) = "CELL_META" # == example # names(CELL_META) names.CELL_META = function(x) { - c("xlim", "ylim", "xrange", "yrange", "xcenter", "ycenter", "cell.xlim", "cell.ylim", + sector.index = get.current.sector.index() + track.index = get.current.track.index() + + nm = c("xlim", "ylim", "xrange", "yrange", "xcenter", "ycenter", "cell.xlim", "cell.ylim", "sector.numeric.index", "sector.index", "track.index", "xplot", "yplot", "cell.width", "cell.height", "track.margin", "cell.padding", "cell.start.degree", "cell.end.degree", "cell.bottom.radius", "cell.top.radius", "bg.col", "bg.border", "bg.lty", "bg.lwd", "track.height") + + env = circos.par("__tempenv__") + if(track.index > 0) { + if(!is.null(env$track.meta.data)) { + track.index = as.character(track.index) + if(!is.null(env$track.meta.data[[track.index]])) { + nm = c(nm, names(env$track.meta.data[[track.index]])) + } + } + } + if(!is.null(sector.index)) { + if(!is.null(env$sector.meta.data)) { + if(!is.null(env$sector.meta.data[[sector.index]])) { + nm = c(nm, names(env$sector.meta.data[[sector.index]])) + } + } + } + + return(nm) } # == title diff --git a/R/plot.R b/R/plot.R index c4043b56..f69d4789 100755 --- a/R/plot.R +++ b/R/plot.R @@ -2651,3 +2651,207 @@ circos.dendrogram = function( draw.d(dend, max_height, facing, max_width = n) } + +# == title +# Draw boxplots +# +# == param +# -value A numeric vector, a matrix or a list. If it is a matrix, boxplots are made by columns. +# -pos Positions of the boxes. +# -outline Whether to draw outliers. +# -box_width Width of boxes. +# -col Filled color of boxes. +# -border Color for the border as well as the quantile lines. +# -lwd Line width. +# -lty Line style +# -cex Point size. +# -pch Point type. +# -pt.col Point color +# +# == example +# circos.initialize(fa = letters[1:4], xlim = c(0, 10)) +# circos.track(ylim = c(0, 1), panel.fun = function(x, y) { +# for(pos in seq(0.5, 9.5, by = 1)) { +# value = runif(10) +# circos.boxplot(value, pos) +# } +# }) +# circos.clear() +# +# circos.initialize(fa = letters[1:4], xlim = c(0, 10)) +# circos.track(ylim = c(0, 1), panel.fun = function(x, y) { +# value = replicate(runif(10), n = 10, simplify = FALSE) +# circos.boxplot(value, 1:10 - 0.5, col = 1:10) +# }) +# circos.clear() +circos.boxplot = function(value, pos, outline = TRUE, box_width = 0.6, + col = NA, border = "black", lwd = par("lwd"), lty = par("lty"), + cex = par("cex"), pch = 1, pt.col = par("col")) { + + single_boxplot = function(value, pos, outline = TRUE, box_width = 0.6, + col = NA, border = "black", lwd = par("lwd"), lty = par("lty"), + cex = par("cex"), pch = 1, pt.col = par("col")) { + + boxplot_stats = boxplot(value, plot = FALSE)$stats + box_height = boxplot_stats[4, 1] - boxplot_stats[2, 1] + + circos.rect(pos - 0.5* box_width, boxplot_stats[2, 1], pos + 0.5 * box_width, boxplot_stats[4, 1], + col = col, border = border, lty = lty, lwd = lwd) + circos.segments(pos - 0.5 * box_width, boxplot_stats[5, 1], pos + 0.5 * box_width, boxplot_stats[5, 1], + col = border, lty = lty, lwd = lwd) + circos.segments(pos, boxplot_stats[5, 1], pos, boxplot_stats[4, 1], + col = border, lty = lty, lwd = lwd) + circos.segments(pos, boxplot_stats[1, 1], pos, boxplot_stats[2, 1], + col = border, lty = lty, lwd = lwd) + circos.segments(pos - 0.5 * box_width, boxplot_stats[1, 1], pos + 0.5 * box_width, boxplot_stats[1, 1], + col = border, lty = lty, lwd = lwd) + circos.segments(pos - 0.5 * box_width, boxplot_stats[3, 1], pos + 0.5 * box_width, boxplot_stats[3, 1], + col = border, lty = lty, lwd = lwd) + if (outline) { + l1 = value > boxplot_stats[5, 1] + if (any(l1)) circos.points(x = rep(pos, sum(l1)), y = value[l1], cex = cex, col = pt.col, pch = pch) + l2 = value < boxplot_stats[1, 1] + if (any(l2)) circos.points(x = rep(pos, sum(l2)), y = value[l2], cex = cex, col = pt.col, pch = pch) + } + } + + if(is.matrix(value)) { + value = as.data.frame(value) + } + + if(is.list(value)) { + n = length(value) + if(length(pos) != n) { + stop_wrap("Length of `pos` should be same as number of boxes.") + } + + if(length(col) == 1) col = rep(col, n) + if(length(border) == 1) border = rep(border, n) + if(length(lwd) == 1) lwd = rep(lwd, n) + if(length(lty) == 1) lty = rep(lty, n) + if(length(cex) == 1) cex = rep(cex, n) + if(length(pch) == 1) pch = rep(pch, n) + if(length(pt.col) == 1) pt.col = rep(pt.col, n) + + for(i in 1:n) { + single_boxplot(value[[i]], pos = pos[i], outline = outline, box_width = box_width, + col = col[i], border = border[i], lwd = lwd[i], lty = lty[i], cex = cex[i], + pch = pch[i], pt.col = pt.col[i]) + } + } else if(is.atomic(value)) { + single_boxplot(value, pos = pos, outline = outline, box_width = box_width, + col = col, border = border, lwd = lwd, lty = lty, cex = cex, pch = pch, pt.col = pt.col) + } +} + +# == title +# Draw violin plots +# +# == param +# -value A numeric vector, a matrix or a list. If it is a matrix, boxplots are made by columns. +# -pos Positions of the boxes. +# -violin_width Width of violins. +# -col Filled color of boxes. +# -border Color for the border as well as the quantile lines. +# -lwd Line width. +# -lty Line style +# -show_quantile Whether to show the quantile lines. +# -cex Point size. +# -pch Point type. +# -pt.col Point color +# -max_density The maximal density value across several violins. It is used to compare between violins. +# +# == example +# circos.initialize(fa = letters[1:4], xlim = c(0, 10)) +# circos.track(ylim = c(0, 1), panel.fun = function(x, y) { +# for(pos in seq(0.5, 9.5, by = 1)) { +# value = runif(10) +# circos.violin(value, pos) +# } +# }) +# circos.clear() +# +# circos.initialize(fa = letters[1:4], xlim = c(0, 10)) +# circos.track(ylim = c(0, 1), panel.fun = function(x, y) { +# value = replicate(runif(10), n = 10, simplify = FALSE) +# circos.violin(value, 1:10 - 0.5, col = 1:10) +# }) +# circos.clear() +circos.violin = function(value, pos, violin_width = 0.8, + col = NA, border = "black", lwd = par("lwd"), lty = par("lty"), + show_quantile = TRUE, pt.col = par("col"), cex = par("cex"), pch = 16, + max_density = NULL) { + + single_violin = function(density, pos, violin_width = 0.8, + col = NA, border = "black", lwd = par("lwd"), lty = par("lty"), + show_quantile = TRUE, pt.col = par("col"), cex = par("cex"), pch = 16, + max_d = max(density$y), value = NULL) { + + y = density$x + x = density$y + + x = x/max_d * (violin_width/2) + y = c(y, rev(y)) + x = c(-x + pos, rev(x + pos)) + box_stat = boxplot(value, plot = FALSE)$stat + + circos.polygon(x, y, border = border, col = col, lwd = lwd, lty = lty) + if(show_quantile) { + circos.lines(c(pos, pos), box_stat[1:2, 1]) + circos.lines(x = c(pos, pos), y = box_stat[4:5, 1]) + circos.points(pos, box_stat[3, 1], cex = cex, col = pt.col, pch = pch) + } + } + + if(is.matrix(value)) { + value = as.data.frame(value) + } + + if(is.list(value)) { + n = length(value) + if(length(pos) != n) { + stop_wrap("Length of `pos` should be same as number of violins.") + } + + if(length(col) == 1) col = rep(col, n) + if(length(border) == 1) border = rep(border, n) + if(length(lwd) == 1) lwd = rep(lwd, n) + if(length(lty) == 1) lty = rep(lty, n) + if(length(cex) == 1) cex = rep(cex, n) + if(length(pch) == 1) pch = rep(pch, n) + if(length(pt.col) == 1) pt.col = rep(pt.col, n) + + density_list = lapply(value, density, na.rm = TRUE) + + for(i in seq_along(density_list)) { + density = density_list[[i]] + l = density$x >= min(value[[i]], na.rm = TRUE) & density$x <= max(value[[i]], na.rm = TRUE); l[is.na(l)] = FALSE + density$x = density$x[l] + density$y = density$y[l] + density_list[[i]] = density + } + + max_d = max(sapply(density_list, function(d) max(d$y))) + if(!is.null(max_density)) max_d = max_density + + for(i in 1:n) { + single_violin(density_list[[i]], pos = pos[i], violin_width = violin_width, + col = col[i], border = border[i], lwd = lwd[i], lty = lty[i], + show_quantile = show_quantile, pt.col = pt.col[i], cex = cex[i], pch = pch[i], + max_d = max_d, value = value[[i]]) + } + } else if(is.atomic(value)) { + density = density(value, na.rm = TRUE) + l = density$x >= min(value, na.rm = TRUE) & density$x <= max(value, na.rm = TRUE); l[is.na(l)] = FALSE + density$x = density$x[l] + density$y = density$y[l] + max_d = max(density$y) + if(!is.null(max_density)) max_d = max_density + + single_violin(density, pos = pos, violin_width = violin_width, + col = col, border = border, lwd = lwd, lty = lty, + show_quantile = show_quantile, pt.col = pt.col, cex = cex, pch = pch, + max_d = max(density$y), value = value) + } +} + diff --git a/man/circos.boxplot.Rd b/man/circos.boxplot.Rd new file mode 100644 index 00000000..fff76bf6 --- /dev/null +++ b/man/circos.boxplot.Rd @@ -0,0 +1,45 @@ +\name{circos.boxplot} +\alias{circos.boxplot} +\title{ +Draw boxplots +} +\description{ +Draw boxplots +} +\usage{ +circos.boxplot(value, pos, outline = TRUE, box_width = 0.6, + col = NA, border = "black", lwd = par("lwd"), lty = par("lty"), + cex = par("cex"), pch = 1, pt.col = par("col")) +} +\arguments{ + + \item{value}{A numeric vector, a matrix or a list. If it is a matrix, boxplots are made by columns.} + \item{pos}{Positions of the boxes.} + \item{outline}{Whether to draw outliers.} + \item{box_width}{Width of boxes.} + \item{col}{Filled color of boxes.} + \item{border}{Color for the border as well as the quantile lines.} + \item{lwd}{Line width.} + \item{lty}{Line style} + \item{cex}{Point size.} + \item{pch}{Point type.} + \item{pt.col}{Point color} + +} +\examples{ +circos.initialize(fa = letters[1:4], xlim = c(0, 10)) +circos.track(ylim = c(0, 1), panel.fun = function(x, y) { + for(pos in seq(0.5, 9.5, by = 1)) { + value = runif(10) + circos.boxplot(value, pos) + } +}) +circos.clear() + +circos.initialize(fa = letters[1:4], xlim = c(0, 10)) +circos.track(ylim = c(0, 1), panel.fun = function(x, y) { + value = replicate(runif(10), n = 10, simplify = FALSE) + circos.boxplot(value, 1:10 - 0.5, col = 1:10) +}) +circos.clear() +} diff --git a/man/circos.heatmap.Rd b/man/circos.heatmap.Rd new file mode 100644 index 00000000..9c67ca80 --- /dev/null +++ b/man/circos.heatmap.Rd @@ -0,0 +1,68 @@ +\name{circos.heatmap} +\alias{circos.heatmap} +\title{ +Make circular heatmaps +} +\description{ +Make circular heatmaps +} +\usage{ +circos.heatmap(x, split = NULL, col, na.col = "grey", + ignore_white = TRUE, default.par = TRUE, + cluster = TRUE, clustering.method = "complete", distance.method = "euclidean", + dend.side = c("none", "outside", "inside"), dend.track.height = 0.1, + rownames.side = c("none", "outside", "inside"), + rownames.cex = 0.5, + rownames.font = par("font"), + ...) +} +\arguments{ + + \item{x}{A matrix or a list of matrices. If the value is a vector, it is converted into a one-column matrix.} + \item{split}{A categorical variable. If the \code{x} is a matrix, it splits the matrix into a list of matrices.} + \item{col}{If the values in the matrices are continuous, the color should be a color mapping generated by \code{\link{colorRamp2}}. If the values are characters, the color should be a named color vector.} + \item{na.col}{Color for \code{NA} values.} + \item{ignore_white}{Whether to draw the white color?} + \item{default.par}{By default \code{\link{circos.par}} is set as \code{cell.padding = c(0, 0, 0, 0), track.margin = c(0.02, 0), gap.degree = 2}. Set this value to \code{FALSE} to use your own \code{\link{circos.par}}.} + \item{cluster}{whether to apply clustering on rows.} + \item{clustering.method}{Clustering method, pass to \code{\link[stats]{hclust}}.} + \item{distance.method}{Distance method, pass to \code{\link[stats]{dist}}.} + \item{dend.side}{Side of the dendrograms relative to the heatmap track.} + \item{dend.track.height}{Track height of the dendrograms.} + \item{rownames.side}{Side of the row names relative to the heatmap track.} + \item{rownames.cex}{Cex of row names.} + \item{rownames.font}{Font of row names.} + \item{...}{Pass to \code{\link{circos.track}} which draws the heatmap track.} + +} +\examples{ +set.seed(123) +mat = matrix(rnorm(1000), nr = 100) +rownames(mat) = paste0("R", 1:100) +split = rep(letters[1:5], times = 10) + +circos.clear() +circos.heatmap(mat, split = split, + col = colorRamp2(c(-2, 0, 2), c("blue", "white", "red"))) + +row_mean = rowMeans(mat) +circos.track(ylim = range(row_mean), panel.fun = function(x, y) { + y = row_mean[split == CELL_META$sector.index] + y = y[CELL_META$row_order] + circos.lines(CELL_META$cell.xlim, c(0, 0), lty = 2, col = "grey") + circos.points(seq_along(y) - 0.5, y, col = ifelse(y > 0, "red", "blue")) +}, cell.padding = c(0.02, 0, 0.02, 0)) +circos.clear() + +circos.clear() +circos.heatmap.initialize(mat, split = split) +row_mean = rowMeans(mat) +circos.track(ylim = range(row_mean), panel.fun = function(x, y) { + y = row_mean[split == CELL_META$sector.index] + y = y[CELL_META$row_order] + circos.lines(CELL_META$cell.xlim, c(0, 0), lty = 2, col = "grey") + circos.points(seq_along(y) - 0.5, y, col = ifelse(y > 0, "red", "blue")) +}, cell.padding = c(0.02, 0, 0.02, 0)) +circos.heatmap(mat, col = colorRamp2(c(-2, 0, 2), c("blue", "white", "red"))) +circos.clear() +} diff --git a/man/circos.heatmap.initialize.Rd b/man/circos.heatmap.initialize.Rd new file mode 100644 index 00000000..cc0690ed --- /dev/null +++ b/man/circos.heatmap.initialize.Rd @@ -0,0 +1,26 @@ +\name{circos.heatmap.initialize} +\alias{circos.heatmap.initialize} +\title{ +Initialize circular heatmaps +} +\description{ +Initialize circular heatmaps +} +\usage{ +circos.heatmap.initialize(x, split = NULL, cluster = TRUE, + clustering.method = "complete", distance.method = "euclidean") +} +\arguments{ + + \item{x}{A matrix or a list of matrices. If the value is a vector, it is converted into a one-column matrix.} + \item{split}{A categorical variable. If the \code{x} is a matrix, it splits the matrix into a list of matrices.} + \item{cluster}{whether to apply clustering on rows.} + \item{clustering.method}{Clustering method, pass to \code{\link[stats]{hclust}}.} + \item{distance.method}{Distance method, pass to \code{\link[stats]{dist}}.} + +} +\examples{ +# There is no example +NULL + +} diff --git a/man/circos.violin.Rd b/man/circos.violin.Rd new file mode 100644 index 00000000..bb2d86ca --- /dev/null +++ b/man/circos.violin.Rd @@ -0,0 +1,47 @@ +\name{circos.violin} +\alias{circos.violin} +\title{ +Draw violin plots +} +\description{ +Draw violin plots +} +\usage{ +circos.violin(value, pos, violin_width = 0.8, + col = NA, border = "black", lwd = par("lwd"), lty = par("lty"), + show_quantile = TRUE, pt.col = par("col"), cex = par("cex"), pch = 16, + max_density = NULL) +} +\arguments{ + + \item{value}{A numeric vector, a matrix or a list. If it is a matrix, boxplots are made by columns.} + \item{pos}{Positions of the boxes.} + \item{violin_width}{Width of violins.} + \item{col}{Filled color of boxes.} + \item{border}{Color for the border as well as the quantile lines.} + \item{lwd}{Line width.} + \item{lty}{Line style} + \item{show_quantile}{Whether to show the quantile lines.} + \item{cex}{Point size.} + \item{pch}{Point type.} + \item{pt.col}{Point color} + \item{max_density}{The maximal density value across several violins. It is used to compare between violins.} + +} +\examples{ +circos.initialize(fa = letters[1:4], xlim = c(0, 10)) +circos.track(ylim = c(0, 1), panel.fun = function(x, y) { + for(pos in seq(0.5, 9.5, by = 1)) { + value = runif(10) + circos.violin(value, pos) + } +}) +circos.clear() + +circos.initialize(fa = letters[1:4], xlim = c(0, 10)) +circos.track(ylim = c(0, 1), panel.fun = function(x, y) { + value = replicate(runif(10), n = 10, simplify = FALSE) + circos.violin(value, 1:10 - 0.5, col = 1:10) +}) +circos.clear() +} diff --git a/man/get.cell.meta.data.Rd b/man/get.cell.meta.data.Rd index f61e2a9f..3518f115 100644 --- a/man/get.cell.meta.data.Rd +++ b/man/get.cell.meta.data.Rd @@ -32,7 +32,7 @@ The following meta information for a cell can be obtained: \item{\code{ycenter}}{Center of y-axis } \item{\code{cell.xlim}}{Minimal and maximal values on the x-axis extended by cell paddings } \item{\code{cell.ylim}}{Minimal and maximal values on the y-axis extended by cell paddings } - \item{\code{xplot}}{Degrees for right and left borders of the cell. } + \item{\code{xplot}}{Degrees for right and left borders of the cell. The values ignore the direction of the circular layout (i.e. whether it is clock wise or not). } \item{\code{yplot}}{Radius for top and bottom borders of the cell. } \item{\code{cell.width}}{Width of the cell, in degrees. } \item{\code{cell.height}}{Height of the cell, simply \code{yplot[2] - yplot[1]} }