R/semi_pheatmap.R
ae4c10aa
 # Adapted originally from the very excellent pheatmap package
 # (https://cran.r-project.org/web/packages/pheatmap/index.html)
 
d7196f24
 #' @importFrom gtable gtable
b26d22a2
 .lo <- function(rown,
     coln,
     nrow,
     ncol,
     cellHeight = NA,
     cellWidth = NA,
     treeHeightCol,
     treeHeightRow,
     legend,
     annotationRow,
     annotationCol,
     annotationColors,
     annotationLegend,
     annotationNamesRow,
     annotationNamesCol,
     main,
     fontSize,
     fontSizeRow,
     fontSizeCol,
     gapsRow,
     gapsCol,
     ...) {
ae4c10aa
     # Get height of colnames and length of rownames
b26d22a2
     if (!is.null(coln[1]) |
9c6ba642
             (!.is.na2(annotationRow) & annotationNamesRow)) {
b26d22a2
         if (!is.null(coln[1])) {
             t <- coln
ae4c10aa
         } else {
b26d22a2
             t <- ""
ae4c10aa
         }
b26d22a2
         tw <- strwidth(t, units = "in", cex = fontSizeCol / fontSize)
         if (annotationNamesRow) {
             t <- c(t, colnames(annotationRow))
             tw <- c(tw, strwidth(colnames(annotationRow), units = "in"))
ae4c10aa
         }
b26d22a2
         longestColn <- which.max(tw)
         gp <- list(fontSize = ifelse(longestColn <= length(coln),
             fontSizeCol,
             fontSize), ...)
         colnHeight <- unit(1,
             "grobheight",
             textGrob(t[longestColn],
                 rot = 90,
                 gp = do.call(gpar, gp))) +
             unit(10, "bigpts")
     } else {
         colnHeight <- unit(5, "bigpts")
ae4c10aa
     }
b26d22a2
 
     if (!is.null(rown[1])) {
         t <- rown
         tw <- strwidth(t, units = "in", cex = fontSizeRow / fontSize)
         if (annotationNamesCol) {
             t <- c(t, colnames(annotationCol))
             tw <- c(tw, strwidth(colnames(annotationCol), units = "in"))
ae4c10aa
         }
b26d22a2
         longestRown <- which.max(tw)
         gp <- list(fontSize = ifelse(longestRown <= length(rown),
             fontSizeRow,
             fontSize), ...)
         rownWidth <- unit(1,
             "grobwidth",
             textGrob(t[longestRown],
                 gp = do.call(gpar, gp))) +
             unit(10, "bigpts")
     } else {
         rownWidth <- unit(5, "bigpts")
ae4c10aa
     }
b26d22a2
 
     gp <- list(fontSize = fontSize, ...)
ae4c10aa
     # Legend position
9c6ba642
     if (!.is.na2(legend)) {
b26d22a2
         longestBreak <- which.max(nchar(names(legend)))
         longestBreak <- unit(1.1,
                 "grobwidth",
                 textGrob(as.character(names(legend))[longestBreak],
                     gp = do.call(gpar, gp)))
         titleLength <- unit(1.1,
             "grobwidth",
             textGrob("Scale",
                 gp = gpar(fontface = "bold",
                     ...)))
         legendWidth <- unit(12, "bigpts") + longestBreak * 1.2
         legendWidth <- max(titleLength, legendWidth)
     } else {
         legendWidth <- unit(0, "bigpts")
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     # Set main title height
b26d22a2
     if (is.na(main)) {
         mainHeight <- unit(0, "npc")
     } else {
         mainHeight <- unit(1.5,
             "grobheight",
             textGrob(main,
                 gp = gpar(fontSize = 1.3 * fontSize,
                     ...)))
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     # Column annotations
b26d22a2
     textheight <- unit(fontSize, "bigpts")
 
9c6ba642
     if (!.is.na2(annotationCol)) {
b26d22a2
         # Column annotation height
         annotColHeight <-
             ncol(annotationCol) *
             (textheight + unit(2, "bigpts")) +
             unit(2, "bigpts")
 
ae4c10aa
         # Width of the correponding legend
b26d22a2
         t <- c(as.vector(as.matrix(annotationCol)), colnames(annotationCol))
         annotColLegendWidth <- unit(1.2,
             "grobwidth",
             textGrob(t[which.max(nchar(t))],
                 gp = gpar(...))) +
             unit(12, "bigpts")
         if (!annotationLegend) {
             annotColLegendWidth <- unit(0, "npc")
ae4c10aa
         }
b26d22a2
     } else {
         annotColHeight <- unit(0, "bigpts")
         annotColLegendWidth <- unit(0, "bigpts")
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     # Row annotations
9c6ba642
     if (!.is.na2(annotationRow)) {
b26d22a2
         # Row annotation width
         annotRowWidth <- ncol(annotationRow) *
             (textheight + unit(2, "bigpts")) +
             unit(2, "bigpts")
 
ae4c10aa
         # Width of the correponding legend
b26d22a2
         t <- c(as.vector(as.matrix(annotationRow)),
             colnames(annotationRow))
         annotRowLegendWidth <- unit(1.2,
             "grobwidth",
             textGrob(t[which.max(nchar(t))],
                 gp = gpar(...))) +
             unit(12,
                 "bigpts")
 
         if (!annotationLegend) {
             annotRowLegendWidth <- unit(0, "npc")
ae4c10aa
         }
b26d22a2
     } else {
         annotRowWidth <- unit(0, "bigpts")
         annotRowLegendWidth <- unit(0, "bigpts")
ae4c10aa
     }
b26d22a2
 
     annotLegendWidth <- max(annotRowLegendWidth, annotColLegendWidth)
 
ae4c10aa
     # Tree height
b26d22a2
     treeHeightCol <- unit(treeHeightCol, "bigpts") + unit(5, "bigpts")
     treeHeightRow <- unit(treeHeightRow, "bigpts") + unit(5, "bigpts")
 
ae4c10aa
     # Set cell sizes
b26d22a2
     if (is.na(cellWidth)) {
         matWidth <- unit(1, "npc") -
             rownWidth -
             legendWidth -
             treeHeightRow -
             annotRowWidth -
             annotLegendWidth
     } else {
         matWidth <- unit(cellWidth * ncol, "bigpts") +
             length(gapsCol) *
             unit(0, "bigpts")
ae4c10aa
     }
b26d22a2
 
     if (is.na(cellHeight)) {
         matHeight <- unit(1, "npc") -
             mainHeight -
             colnHeight -
             treeHeightCol -
             annotColHeight
     } else {
         matHeight <- unit(cellHeight * nrow, "bigpts") +
             length(gapsRow) *
             unit(0, "bigpts")
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     # Produce gtable
d7196f24
     gt <- gtable::gtable(widths = unit.c(treeHeightRow,
b26d22a2
             annotRowWidth,
             matWidth,
             rownWidth,
             legendWidth,
             annotLegendWidth),
         heights = unit.c(mainHeight,
             treeHeightCol,
             annotColHeight,
             matHeight,
             colnHeight),
         vp = viewport(gp = do.call(gpar, gp)))
 
     cw <- convertWidth(matWidth -
         (length(gapsCol) * unit(0, "bigpts")),
         "bigpts", valueOnly = TRUE) / ncol
     ch <- convertHeight(matHeight -
         (length(gapsRow) * unit(0, "bigpts")),
         "bigpts", valueOnly = TRUE) / nrow
 
ae4c10aa
     # Return minimal cell dimension in bigpts to decide if borders are drawn
b26d22a2
     mindim <- min(cw, ch)
 
     res <- list(gt = gt, mindim = mindim)
 
ae4c10aa
     return(res)
 }
 
b6cf56ae
 .findCoordinates <- function(n, gaps, m = seq(1, n)) {
b26d22a2
     if (length(gaps) == 0) {
         return(list(
             coord = unit(m / n, "npc"),
             size = unit(1 / n, "npc")))
ae4c10aa
     }
b26d22a2
 
     if (max(gaps) > n) {
ae4c10aa
         stop("Gaps do not match with matrix size")
     }
b26d22a2
 
     size <- (1 / n) *
         (unit(1, "npc") - length(gaps) * unit("0", "bigpts"))
 
92ca710a
     gaps2 <- base::apply(vapply(gaps,
b6cf56ae
         function(gap, x) {
             x > gap
         },
92ca710a
         integer(n), m), 1, sum)
b26d22a2
     coord <- m * size + (gaps2 * unit("0", "bigpts"))
 
ae4c10aa
     return(list(coord = coord, size = size))
 }
 
9c6ba642
 .drawDendrogram <- function(hc, gaps, horizontal = TRUE) {
b26d22a2
     h <- hc$height / max(hc$height) / 1.05
     m <- hc$merge
     o <- hc$order
     n <- length(o)
ae4c10aa
 
b26d22a2
     m[m > 0] <- n + m[m > 0]
     m[m < 0] <- abs(m[m < 0])
ae4c10aa
 
b26d22a2
     dist <- matrix(0,
         nrow = 2 * n - 1,
         ncol = 2,
         dimnames = list(NULL, c("x", "y")))
b6cf56ae
     dist[seq(1, n), 1] <- 1 / n / 2 + (1 / n) *
         (match(seq(1, n), o) - 1)
ae4c10aa
 
b6cf56ae
     for (i in seq(1, nrow(m))) {
b26d22a2
         dist[n + i, 1] <- (dist[m[i, 1], 1] + dist[m[i, 2], 1]) / 2
         dist[n + i, 2] <- h[i]
ae4c10aa
     }
b26d22a2
 
     drawConnection <- function(x1, x2, y1, y2, y) {
         res <- list(x = c(x1, x1, x2, x2),
             y = c(y1, y, y, y2))
 
ae4c10aa
         return(res)
     }
b26d22a2
 
     x <- rep(NA, nrow(m) * 4)
     y <- rep(NA, nrow(m) * 4)
b6cf56ae
     id <- rep(seq(nrow(m)), rep(4, nrow(m)))
b26d22a2
 
b6cf56ae
     for (i in seq(1, nrow(m))) {
b26d22a2
         c <- drawConnection(dist[m[i, 1], 1],
             dist[m[i, 2], 1],
             dist[m[i, 1], 2],
             dist[m[i, 2], 2],
             h[i])
         k <- (i - 1) * 4 + 1
         x[seq(k, k + 3)] <- c$x
         y[seq(k, k + 3)] <- c$y
ae4c10aa
     }
b26d22a2
 
9c6ba642
     x <- .findCoordinates(n, gaps, x * n)$coord
b26d22a2
     y <- unit(y, "npc")
 
     if (!horizontal) {
         a <- x
         x <- unit(1, "npc") - y
         y <- unit(1, "npc") - a
ae4c10aa
     }
b26d22a2
     res <- polylineGrob(x = x, y = y, id = id)
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .drawMatrix <- function(matrix,
b26d22a2
     borderColor,
     gapsRows,
     gapsCols,
     fmat,
     fontSizeNumber,
     numberColor) {
 
     n <- nrow(matrix)
     m <- ncol(matrix)
 
9c6ba642
     coordX <- .findCoordinates(m, gapsCols)
     coordY <- .findCoordinates(n, gapsRows)
b26d22a2
 
     x <- coordX$coord -
         0.5 * coordX$size
     y <- unit(1, "npc") -
         (coordY$coord - 0.5 * coordY$size)
 
     coord <- expand.grid(y = y, x = x)
 
     res <- gList()
 
     res[["rect"]] <- rectGrob(x = coord$x,
         y = coord$y,
         width = coordX$size,
         height = coordY$size,
         gp = gpar(fill = matrix, col = borderColor))
 
     if (attr(fmat, "draw")) {
         res[["text"]] <- textGrob(x = coord$x,
             y = coord$y,
             label = fmat,
             gp = gpar(col = numberColor, fontSize = fontSizeNumber))
ae4c10aa
     }
b26d22a2
 
     res <- gTree(children = res)
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .drawColnames <- function(coln, gaps, ...) {
     coord <- .findCoordinates(length(coln), gaps)
b26d22a2
     x <- coord$coord - 0.5 * coord$size
 
     res <- textGrob(coln,
         x = x,
         y = unit(1, "npc") -
             unit(3, "bigpts"),
         vjust = 0.5,
         hjust = 0,
         rot = 270,
         gp = gpar(...))
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .drawRownames <- function(rown, gaps, ...) {
     coord <- .findCoordinates(length(rown), gaps)
b26d22a2
     y <- unit(1, "npc") - (coord$coord - 0.5 * coord$size)
 
     res <- textGrob(rown,
             x = unit(3, "bigpts"),
             y = y,
             vjust = 0.5,
             hjust = 0,
             gp = gpar(...))
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .drawLegend <- function(color, breaks, legend, ...) {
b26d22a2
     height <- min(unit(1, "npc"), unit(150, "bigpts"))
 
     legendPos <- (legend - min(breaks)) / (max(breaks) - min(breaks))
     legendPos <- height * legendPos + (unit(1, "npc") - height)
 
     breaks <- (breaks - min(breaks)) / (max(breaks) - min(breaks))
     breaks <- height * breaks + (unit(1, "npc") - height)
 
     h <- breaks[-1] - breaks[-length(breaks)]
 
     rect <- rectGrob(x = 0,
         y = breaks[-length(breaks)],
         width = unit(10, "bigpts"),
         height = h,
         hjust = 0,
         vjust = 0,
         gp = gpar(fill = color, col = "#FFFFFF00"))
 
     text <- textGrob(names(legend),
         x = unit(14, "bigpts"),
         y = legendPos,
         hjust = 0,
         gp = gpar(...))
 
     res <- grobTree(rect, text)
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .convertAnnotations <- function(annotation, annotationColors) {
b26d22a2
     new <- annotation
92ca710a
     for (i in seq(ncol(annotation))) {
b26d22a2
         a <- annotation[, i]
         b <- annotationColors[[colnames(annotation)[i]]]
         if (is.character(a) | is.factor(a)) {
             a <- as.character(a)
 
             if (length(setdiff(setdiff(a, NA), names(b))) > 0) {
                 stop(sprintf("Factor levels on variable %s do not match
                         with annotationColors",
                     colnames(annotation)[i]))
ae4c10aa
             }
b26d22a2
             new[, i] <- b[a]
         } else {
             a <- cut(a, breaks = 100)
             new[, i] <- colorRampPalette(b)(100)[a]
ae4c10aa
         }
     }
     return(as.matrix(new))
 }
 
9c6ba642
 .drawAnnotations <- function(convertedAnnotations,
b26d22a2
     borderColor,
     gaps,
     fontSize,
     horizontal) {
 
     n <- ncol(convertedAnnotations)
     m <- nrow(convertedAnnotations)
 
9c6ba642
     coordX <- .findCoordinates(m, gaps)
b26d22a2
 
     x <- coordX$coord - 0.5 * coordX$size
 
     # y = cumsum(rep(fontSize, n)) - 4 + cumsum(rep(2, n))
     y <- cumsum(rep(fontSize, n)) +
         cumsum(rep(2, n)) -
         fontSize / 2 + 1
     y <- unit(y, "bigpts")
 
     if (horizontal) {
         coord <- expand.grid(x = x, y = y)
         res <- rectGrob(x = coord$x,
             y = coord$y,
             width = coordX$size,
             height = unit(fontSize, "bigpts"),
             gp = gpar(fill = convertedAnnotations, col = borderColor))
     } else {
         a <- x
         x <- unit(1, "npc") - y
         y <- unit(1, "npc") - a
 
         coord <- expand.grid(y = y, x = x)
         res <- rectGrob(x = coord$x,
             y = coord$y,
             width = unit(fontSize, "bigpts"),
             height = coordX$size,
             gp = gpar(fill = convertedAnnotations, col = borderColor))
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .drawAnnotationNames <- function(annotations, fontSize, horizontal) {
b26d22a2
     n <- ncol(annotations)
 
     x <- unit(3, "bigpts")
 
     y <- cumsum(rep(fontSize, n)) +
         cumsum(rep(2, n)) -
         fontSize / 2 + 1
 
     y <- unit(y, "bigpts")
 
     if (horizontal) {
         res <- textGrob(colnames(annotations),
             x = x,
             y = y,
             hjust = 0,
             gp = gpar(fontSize = fontSize, fontface = 2))
     } else {
         a <- x
         x <- unit(1, "npc") - y
         y <- unit(1, "npc") - a
 
         res <- textGrob(colnames(annotations),
             x = x,
             y = y,
             vjust = 0.5,
             hjust = 0,
             rot = 270,
             gp = gpar(fontSize = fontSize, fontface = 2))
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .drawAnnotationLegend <- function(annotation,
b26d22a2
     annotationColors,
     borderColor,
     ...) {
 
     y <- unit(1, "npc")
     textHeight <- unit(1,
         "grobheight",
         textGrob("FGH", gp = gpar(...)))
 
     res <- gList()
     for (i in names(annotation)) {
         res[[i]] <- textGrob(i,
             x = 0,
             y = y,
             vjust = 1,
             hjust = 0,
             gp = gpar(fontface = "bold", ...))
 
         y <- y - 1.5 * textHeight
         if (is.character(annotation[[i]]) |
                 is.factor(annotation[[i]])) {
             n <- length(annotationColors[[i]])
92ca710a
             yy <- y - (seq(n) - 1) * 2 * textHeight
b26d22a2
 
             res[[paste(i, "r")]] <- rectGrob(x = unit(0, "npc"),
                 y = yy,
                 hjust = 0,
                 vjust = 1,
                 height = 2 * textHeight,
                 width = 2 * textHeight,
                 gp = gpar(col = borderColor, fill = annotationColors[[i]]))
 
             res[[paste(i, "t")]] <- textGrob(names(annotationColors[[i]]),
                 x = textHeight * 2.4,
                 y = yy - textHeight,
                 hjust = 0,
                 vjust = 0.5,
                 gp = gpar(...))
 
             y <- y - n * 2 * textHeight
         } else {
             yy <- y - 8 * textHeight + seq(0, 1, 0.25)[-1] * 8 * textHeight
             h <- 8 * textHeight * 0.25
 
             res[[paste(i, "r")]] <- rectGrob(x = unit(0, "npc"),
                 y = yy,
                 hjust = 0,
                 vjust = 1,
                 height = h,
                 width = 2 * textHeight,
                 gp = gpar(col = NA,
                         fill = colorRampPalette(annotationColors[[i]])(4)))
             res[[paste(i, "r2")]] <- rectGrob(x = unit(0, "npc"),
                 y = y,
                 hjust = 0,
                 vjust = 1,
                 height = 8 * textHeight,
                 width = 2 * textHeight,
                 gp = gpar(col = borderColor, fill = NA))
 
7890fdf1
             txt <- rev(range(grid::grid.pretty(range(annotation[[i]],
b26d22a2
                 na.rm = TRUE))))
 
             yy <- y - c(1, 7) * textHeight
             res[[paste(i, "t")]] <- textGrob(txt,
                 x = textHeight * 2.4,
                 y = yy,
                 hjust = 0,
                 vjust = 0.5,
                 gp = gpar(...))
             y <- y - 8 * textHeight
ae4c10aa
         }
b26d22a2
         y <- y - 1.5 * textHeight
ae4c10aa
     }
b26d22a2
 
     res <- gTree(children = res)
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .drawMain <- function(text, ...) {
b26d22a2
     res <- textGrob(text, gp = gpar(fontface = "bold", ...))
 
ae4c10aa
     return(res)
 }
 
b26d22a2
 vplayout <- function(x, y) {
ae4c10aa
     return(viewport(layout.pos.row = x, layout.pos.col = y))
 }
 
d7196f24
 #' @importFrom gtable gtable_height
 #' @importFrom gtable gtable_width
 #' @importFrom gtable gtable_add_grob
e3638ca1
 #' @import grDevices
b26d22a2
 .heatmapMotor <- function(matrix,
         borderColor,
         cellWidth,
         cellHeight,
         treeCol,
         treeRow,
         treeHeightCol,
         treeHeightRow,
         fileName,
         width,
         height,
         breaks,
         color,
         legend,
         annotationRow,
         annotationCol,
         annotationColors,
         annotationLegend,
         annotationNamesRow,
         annotationNamesCol,
         main,
         fontSize,
         fontSizeRow,
         fontSizeCol,
         fmat,
         fontSizeNumber,
         numberColor,
         gapsCol,
         gapsRow,
         labelsRow,
         labelsCol,
         ...) {
         # Set layout
         lo <- .lo(coln = labelsCol,
             rown = labelsRow,
             nrow = nrow(matrix),
             ncol = ncol(matrix),
             cellWidth = cellWidth,
             cellHeight = cellHeight,
             treeHeightCol = treeHeightCol,
             treeHeightRow = treeHeightRow,
             legend = legend,
             annotationCol = annotationCol,
             annotationRow = annotationRow,
             annotationColors = annotationColors,
             annotationLegend = annotationLegend,
             annotationNamesRow = annotationNamesRow,
             annotationNamesCol = annotationNamesCol,
             main = main,
             fontSize = fontSize,
             fontSizeRow = fontSizeRow,
             fontSizeCol = fontSizeCol,
             gapsRow = gapsRow,
             gapsCol = gapsCol,
             ...)
 
         res <- lo$gt
         mindim <- lo$mindim
 
         if (!is.na(fileName)) {
             if (is.na(height)) {
d7196f24
                 height <- convertHeight(gtable::gtable_height(res),
b26d22a2
                     "inches",
                     valueOnly = TRUE)
             }
             if (is.na(width)) {
d7196f24
                 width <- convertWidth(gtable::gtable_width(res),
b26d22a2
                     "inches",
                     valueOnly = TRUE)
             }
 
             # Get file type
             r <- regexpr("\\.[a-zA-Z]*$", fileName)
             if (r == -1)
                 stop("Improper fileName")
             ending <- substr(fileName,
                 r + 1,
                 r + attr(r, "match.length"))
 
             f <- switch(ending,
                 pdf = function(x, ...)
                 pdf(x, ...),
                 png = function(x, ...)
                 png(x, units = "in",
                     res = 300, ...),
                 jpeg = function(x, ...)
                 jpeg(x, units = "in",
                     res = 300, ...),
                 jpg = function(x, ...)
                 jpeg(x, units = "in",
                     res = 300, ...),
                 tiff = function(x, ...)
                 tiff(x,
                     units = "in",
                     res = 300,
                     compression = "lzw",
                     ...),
                 bmp = function(x, ...)
                 bmp(x, units = "in",
                     res = 300, ...),
                 stop("File type should be: pdf, png, bmp, jpg, tiff"))
 
             # print(sprintf("height:%f width:%f", height, width))
 
             # gt = .heatmapMotor(matrix,
             #     cellWidth = cellWidth,
             #     cellHeight = cellHeight,
             #     borderColor = borderColor,
             #     treeCol = treeCol,
             #     treeRow = treeRow,
             #     treeHeightCol = treeHeightCol,
             #     treeHeightRow = treeHeightRow,
             #     breaks = breaks,
             #     color = color,
             #     legend = legend,
             #     annotationCol = annotationCol,
             #     annotationRow = annotationRow,
             #     annotationColors = annotationColors,
             #     annotationLegend = annotationLegend,
             #     fileName = NA, main = main,
             #     fontSize = fontSize,
             #     fontSizeRow = fontSizeRow,
             #     fontSizeCol = fontSizeCol,
             #     fmat = fmat,
             #     fontSizeNumber =  fontSizeNumber,
             #     numberColor = numberColor,
             #     labelsRow = labelsRow,
             #     labelsCol = labelsCol,
             #     gapsCol = gapsCol,
             #     gapsRow = gapsRow, ...)
 
             f(fileName, height = height, width = width)
             gt <- .heatmapMotor(matrix,
                 cellWidth = cellWidth,
                 cellHeight = cellHeight,
                 borderColor = borderColor,
                 treeCol = treeCol,
                 treeRow = treeRow,
                 treeHeightCol = treeHeightCol,
                 treeHeightRow = treeHeightRow,
                 breaks = breaks,
                 color = color,
                 legend = legend,
                 annotationCol = annotationCol,
                 annotationRow = annotationRow,
                 annotationColors = annotationColors,
                 annotationLegend = annotationLegend,
                 annotationNamesRow = annotationNamesRow,
                 annotationNamesCol = annotationNamesCol,
                 fileName = NA,
                 main = main,
                 fontSize = fontSize,
                 fontSizeRow = fontSizeRow,
                 fontSizeCol = fontSizeCol,
                 fmat = fmat,
                 fontSizeNumber = fontSizeNumber,
                 numberColor = numberColor,
                 labelsRow = labelsRow,
                 labelsCol = labelsCol,
                 gapsCol = gapsCol,
                 gapsRow = gapsRow,
                 ...)
             grid.draw(gt)
             dev.off()
 
             return(gt)
ae4c10aa
         }
b26d22a2
 
         # Omit border color if cell size is too small
         if (mindim < 3){
             borderColor <- NA
ae4c10aa
         }
b26d22a2
 
         # Draw title
         if (!is.na(main)) {
9c6ba642
             elem <- .drawMain(main, fontSize = 1.3 * fontSize, ...)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = 1,
                 l = 3,
                 name = "main",
                 clip = "off")
ae4c10aa
         }
b26d22a2
 
         # Draw tree for the columns
9c6ba642
         if (!.is.na2(treeCol) & treeHeightCol != 0) {
             elem <- .drawDendrogram(treeCol, gapsCol, horizontal = TRUE)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = 2,
                 l = 3,
                 name = "col_tree")
ae4c10aa
         }
 
b26d22a2
         # Draw tree for the rows
9c6ba642
         if (!.is.na2(treeRow) & treeHeightRow != 0) {
             elem <- .drawDendrogram(treeRow, gapsRow, horizontal = FALSE)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = 4,
                 l = 1,
                 name = "row_tree")
         }
 
         # Draw matrix
9c6ba642
         elem <- .drawMatrix(matrix,
b26d22a2
             borderColor,
             gapsRow,
             gapsCol,
             fmat,
             fontSizeNumber,
             numberColor)
 
d7196f24
         res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = 4,
                 l = 3,
                 clip = "off",
                 name = "matrix")
 
         # Draw colnames
         if (length(labelsCol) != 0) {
             pars <- list(labelsCol,
                 gaps = gapsCol,
                 fontSize = fontSizeCol,
                 ...)
9c6ba642
             elem <- do.call(.drawColnames, pars)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = 5,
                 l = 3,
                 clip = "off",
                 name = "col_names")
         }
 
         # Draw rownames
         if (length(labelsRow) != 0) {
             pars <- list(labelsRow,
                 gaps = gapsRow,
                 fontSize = fontSizeRow, ...)
9c6ba642
             elem <- do.call(.drawRownames, pars)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = 4,
                 l = 4,
                 clip = "off",
                 name = "row_names")
         }
 
         # Draw annotation tracks on cols
9c6ba642
         if (!.is.na2(annotationCol)) {
b26d22a2
             # Draw tracks
9c6ba642
             convertedAnnotation <- .convertAnnotations(annotationCol,
b26d22a2
                 annotationColors)
9c6ba642
             elem <- .drawAnnotations(convertedAnnotation,
b26d22a2
                 borderColor,
                 gapsCol,
                 fontSize,
                 horizontal = TRUE)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = 3,
                 l = 3,
                 clip = "off",
                 name = "col_annotation")
 
             # Draw names
             if (annotationNamesCol) {
9c6ba642
                 elem <- .drawAnnotationNames(annotationCol,
b26d22a2
                     fontSize,
                     horizontal = TRUE)
d7196f24
                 res <- gtable::gtable_add_grob(res,
b26d22a2
                     elem,
                     t = 3,
                     l = 4,
                     clip = "off",
                     name = "col_annotation_names")
             }
         }
 
         # Draw annotation tracks on rows
9c6ba642
         if (!.is.na2(annotationRow)) {
b26d22a2
             # Draw tracks
9c6ba642
             convertedAnnotation <- .convertAnnotations(annotationRow,
b26d22a2
                 annotationColors)
9c6ba642
             elem <- .drawAnnotations(convertedAnnotation,
b26d22a2
                 borderColor,
                 gapsRow,
                 fontSize,
                 horizontal = FALSE)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = 4,
                 l = 2,
                 clip = "off",
                 name = "row_annotation")
 
             # Draw names
             if (annotationNamesRow) {
9c6ba642
                 elem <- .drawAnnotationNames(annotationRow,
b26d22a2
                     fontSize,
                     horizontal = FALSE)
d7196f24
                 res <- gtable::gtable_add_grob(res,
b26d22a2
                     elem,
                     t = 5,
                     l = 2,
                     clip = "off",
                     name = "row_annotation_names")
             }
         }
 
         # Draw annotation legend
         annotation <- c(annotationCol[length(annotationCol):1],
             annotationRow[length(annotationRow):1])
         annotation <- annotation[unlist(lapply(annotation,
9c6ba642
             function(x) !.is.na2(x)))]
b26d22a2
 
         if (length(annotation) > 0 & annotationLegend) {
9c6ba642
             elem <- .drawAnnotationLegend(annotation,
b26d22a2
                 annotationColors,
                 borderColor,
                 fontSize = fontSize,
                 ...)
 
             t <- ifelse(is.null(labelsRow), 4, 3)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                 elem,
                 t = t,
                 l = 6,
                 b = 5,
                 clip = "off",
                 name = "annotationLegend")
         }
 
         # Draw legend
9c6ba642
         if (!.is.na2(legend)) {
             elem <- .drawLegend(color, breaks, legend, fontSize = fontSize, ...)
b26d22a2
 
             t <- ifelse(is.null(labelsRow), 4, 3)
d7196f24
             res <- gtable::gtable_add_grob(res,
b26d22a2
                     elem,
                     t = t,
                     l = 5,
                     b = 5,
                     clip = "off",
                     name = "legend")
         }
 
         return(res)
ae4c10aa
     }
b26d22a2
 
9c6ba642
 .generateBreaks <- function(x, n, center = FALSE) {
b26d22a2
     if (center) {
b6cf56ae
         m <- max(abs(c(min(x, na.rm = TRUE),
b26d22a2
             max(x, na.rm = TRUE))))
         res <- seq(-m, m, length.out = n + 1)
     } else {
         res <- seq(min(x, na.rm = TRUE),
             max(x, na.rm = TRUE),
             length.out = n + 1)
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     return(res)
 }
 
9c6ba642
 .scaleVecColours <- function(x, col = rainbow(10), breaks = NA) {
c424d2d9
     return(col[as.numeric(cut(x, breaks = breaks, include.lowest = TRUE))])
ae4c10aa
 }
 
9c6ba642
 .scaleColours <- function(mat,
b26d22a2
     col = rainbow(10),
     breaks = NA) {
     mat <- as.matrix(mat)
     return(matrix(
9c6ba642
         .scaleVecColours(as.vector(mat), col = col, breaks = breaks),
b26d22a2
             nrow(mat),
             ncol(mat),
             dimnames = list(rownames(mat), colnames(mat))))
ae4c10aa
 }
 
b26d22a2
 ## changed the original clusterMat() in the pheatmap.r
7890fdf1
 #' @importFrom scales hue_pal
9c6ba642
 .clusterMat <- function(mat, labels, distance, method) {
     # this funciton is going to change the .clusterMat() in pheatmap
b26d22a2
 
     if (!(method %in% c("ward.D",
             "ward.D2",
             "ward",
             "single",
             "complete",
             "average",
             "mcquitty",
             "median",
             "centroid"))) {
         stop("clustering method has to one form the list:
             'ward',
             'ward.D',
             'ward.D2',
             'single',
             'complete',
             'average',
             'mcquitty',
             'median'
             or 'centroid'.")
ae4c10aa
     }
b26d22a2
 
     class.label <- unique(labels)
 
     nGroup <- length(class.label) # [#group]
     # get "hclust" object for each group then wrap them up as group.hclust
 
     # distance function preparation
     dis <- function(mat, distance) {
         if (!(distance[1] %in% c("correlation",
                 "euclidean",
                 "maximum",
                 "manhattan",
                 "canberra",
                 "binary",
                 "minkowski")) &
                 !methods::is(distance, "dist")) {
22ad839c
             stop("distance has to be a dissimilarity structure as produced by",
                 " dist or one measure  form the list: 'correlation',",
                 " 'euclidean', 'maximum', 'manhattan', 'canberra', 'binary',",
                 " 'minkowski'")
ae4c10aa
         }
b26d22a2
 
         if (distance[1] == "correlation") {
             # this part should be confirmed whether being wrong?
             #ToDo: how is the correlation matrix converted to a dsit matrix
             d <- stats::as.dist(1 - stats::cor(t(mat)))
         } else {
             d <- stats::dist(mat, method = distance)
         }
 
         return(d)
ae4c10aa
     }
b26d22a2
 
     # initiate the final returning value: a "hclust" object
     cum.hclust <- list()
 
     if (nGroup == 1) {
         # matrix has only 1 group
         if (length(labels) == 1) {
             stop("only one row/column for the matrix")
         }
         group.hclust <- stats::hclust(dis(mat = mat,
                 distance = distance),
             method = method)
 
         cum.hclust <- group.hclust
     } else {
         #  matrix has more than 1 groups
92ca710a
         group.hclust <- vapply(class.label, function(x) {
b26d22a2
             # get the positions of class label
             class.pos <- which(labels == x)
 
             if (length(class.pos) == 1) {
b6cf56ae
                 # if only 1 row in the group return a manually made "hclust"
                 # object
22ad839c
                 sub.hclust <- as.list(seq(7))
b26d22a2
                 names(sub.hclust) <- c("merge",
                     "height",
                     "order",
                     "labels",
                     "method",
                     "call",
                     "dist.method")
 
                 class(sub.hclust) <- "hclust"
                 sub.hclust$merge <- matrix(c(0, 0), nrow = 1)
                 sub.hclust$height <- 0
                 sub.hclust$order <- 1
                 return(sub.hclust)
             } else if (length(class.pos) > 1) {
                 # if >1 rows return the "hclust" object
b6cf56ae
                 return(stats::hclust(dis(mat = mat[class.pos, ],
b26d22a2
                     distance = distance),
                     method = method))
             }
92ca710a
         },
             list("merge" = 0,
                 "height" = 0,
                 "order" = 0,
                 "labels" = 0,
                 "method" = 0,
                 "call" = 0,
                 "dist.method" = 0))
b26d22a2
         # the length(group.hclust) is the [#group] == nGroup   ,
         # group.hclust[[i]] to get each "hclust"
 
         # then modify the "hclust" object and get them merged into one
         # "hclust" object
 
         # initiate the final "hclust" object
         cum.hclust <- group.hclust[, nGroup]
 
         # merge function preparation
         mergeHclust <- function(hclust1, hclust2) {
                 # "hclust" object modifying function preparation
                 if (hclust1$merge[1, 1] == 0 &
                         hclust2$merge[1, 1] == 0) {
                     # both groups have only 1 row
22ad839c
                     hclustCom <- as.list(seq(7))
b26d22a2
                     names(hclustCom) <-
                         c("merge",
                         "height",
                         "order",
                         "labels",
                         "method",
                         "call",
                         "dist.method")
 
                     class(hclustCom) <- "hclust"
b6cf56ae
                     hclustCom$merge <- matrix(c(-1, -2), nrow = 1)
b26d22a2
                     # check for different matrix whether 1 should be good
                     hclustCom$height <- 1
                     hclustCom$order <- c(1, 2)
                     return(hclustCom)
                 } else if (hclust1$merge[1, 1] != 0 &
                         hclust2$merge[1, 1] != 0) {
                     # both group have >1 rows
 
                     # nodes in the hclust1 group, so actually the #rows should
                     # be dim()[1]+1
                     row.1 <- dim(hclust1$merge)[1]
                     # nodes in the hclust2 group
                     row.2 <- dim(hclust2$merge)[1]
                     hclustCom <- list()
                     mer <- hclust2$merge
                     # modify the hclust2$merge matrix
                     hclustCom$merge <- (mer > 0) *
                         (mer + row.1) + (mer < 0) *
                         (mer - row.1 - 1)
                     # combine the merge matrix from the 2 groups
                     hclustCom$merge <- rbind(hclust1$merge,
                         hclustCom$merge)
                     hclustCom$merge <- rbind(hclustCom$merge,
                         c(row.1, row.1 + row.2))
                     hclustCom$height <- c(hclust1$height, hclust2$height)
                     # check for different matrix whether 1 should be good
                     hclustCom$height <- c(hclustCom$height,
                         max(hclustCom$height) + 1)
                     hclustCom$order <- c(hclust1$order,
                         hclust2$order + row.1 + 1)
                     class(hclustCom) <- "hclust"
                 } else {
                     # one group has only 1 row, the other group has >1 rows
                     if (hclust1$merge[1, 1] == 0) {
                         # hclust1 has 1 row , hclust2 has >1 rows
 
                         # nodes in the hclust2 group
                         row.2 <- dim(hclust2$merge)[1]
92ca710a
                         hclustCom <- as.list(seq(7))
b26d22a2
                         names(hclustCom) <- c("merge",
                                 "height",
                                 "order",
                                 "labels",
                                 "method",
                                 "call",
                                 "dist.method")
                         class(hclustCom) <- "hclust"
                         mer <- hclust2$merge
                         hclustCom$merge <- (mer > 0) *
                             (mer) +
                             (mer < 0) *
                             (mer - 1)
                         hclustCom$merge <- rbind(hclustCom$merge,
                             c(-1, row.2))
                         # check for different matrix whether 1 should be good
                         hclustCom$height <- c(hclust2$height,
                             max(hclust2$height) + 1)
                         hclustCom$order <- c(1, hclust2$order + 1)
                     } else if (hclust2$merge[1, 1] == 0) {
                         # the hclust1 has >1 rows , and hclust2 has 1 row
 
                         #nodes in the hclust1 group
                         row.1 <- dim(hclust1$merge)[1]
b6cf56ae
                         hclustCom <- as.list(seq(1, 7))
b26d22a2
                         names(hclustCom) <-
                             c("merge",
                                 "height",
                                 "order",
                                 "labels",
                                 "method",
                                 "call",
                                 "dist.method")
                         class(hclustCom) <- "hclust"
                         hclustCom$merge <- hclust1$merge
                         hclustCom$merge <- rbind(hclustCom$merge,
b6cf56ae
                             c(row.1, - (row.1 + 2)))
b26d22a2
                         hclustCom$height <- c(hclust1$height,
                             max(hclust1$height) + 1)
                         hclustCom$order <- c(hclust1$order,
                             max(hclust1$order) + 1)
                     }
                 }
 
                 return(hclustCom)
             }
 
         # merge the "hclust" object into the final one "hclust" object
         for (i in seq(nGroup - 1, 1, -1)) {
             cum.hclust <- mergeHclust(group.hclust[, i], cum.hclust)
         }
ae4c10aa
     }
b26d22a2
 
     cum.hclust$labels <- NULL
     cum.hclust$call <- NULL
     cum.hclust$method <- NULL
     cum.hclust$dist.method <- NULL
 
     return(cum.hclust)
ae4c10aa
 }
 
9c6ba642
 .scaleRows <- function(x) {
b26d22a2
     m <- base::apply(x, 1, mean, na.rm = TRUE)
     s <- base::apply(x, 1, stats::sd, na.rm = TRUE)
ae4c10aa
     return((x - m) / s)
 }
 
9c6ba642
 .scaleMat <- function(mat, scale) {
b26d22a2
     if (!(scale %in% c("none", "row", "column"))) {
ae4c10aa
         stop("scale argument shoud take values: 'none', 'row' or 'column'")
     }
9c6ba642
     mat <- switch(scale,
b26d22a2
             none = mat,
9c6ba642
             row = .scaleRows(mat),
             column = t(.scaleRows(t(mat))))
ae4c10aa
     return(mat)
 }
 
d7196f24
 #' @importFrom scales dscale
e3638ca1
 #' @importFrom scales brewer_pal
2c8e7d4d
 .generateAnnotationColours <- function(annotation,
9c6ba642
     annotationColors,
     drop) {
 
         if (.is.na2(annotationColors)) {
b26d22a2
             annotationColors <- list()
ae4c10aa
         }
b26d22a2
         count <- 0
92ca710a
         for (i in seq(length(annotation))) {
b26d22a2
             annotation[[i]] <- annotation[[i]][!is.na(annotation[[i]])]
             if (is.character(annotation[[i]]) |
                     is.factor(annotation[[i]])) {
                 if (is.factor(annotation[[i]]) & !drop) {
                     count <- count + length(levels(annotation[[i]]))
                 } else {
                     count <- count + length(unique(annotation[[i]]))
ae4c10aa
                 }
             }
b26d22a2
         }
 
7890fdf1
         factorColors <- scales::dscale(factor(seq(1, count)),
             scales::hue_pal(l = 75))
b26d22a2
 
         contCounter <- 2
92ca710a
         for (i in seq(length(annotation))) {
b26d22a2
             if (!(names(annotation)[i] %in% names(annotationColors))) {
                 if (is.character(annotation[[i]]) |
                         is.factor(annotation[[i]])) {
                     n <- length(unique(annotation[[i]]))
 
                     if (is.factor(annotation[[i]]) & !drop) {
                         n <- length(levels(annotation[[i]]))
                     }
 
92ca710a
                     ind <- sample(seq_along(factorColors), n)
b26d22a2
                     annotationColors[[names(annotation)[i]]] <-
                         factorColors[ind]
                     l <- levels(as.factor(annotation[[i]]))
                     l <- l[l %in% unique(annotation[[i]])]
                     if (is.factor(annotation[[i]]) & !drop) {
                         l <- levels(annotation[[i]])
                     }
 
                     names(annotationColors[[names(annotation)[i]]]) <- l
                     factorColors <- factorColors[-ind]
                 } else {
                     annotationColors[[names(annotation)[i]]] <-
e3638ca1
                         scales::brewer_pal("seq", contCounter)(5)[seq(4)]
b26d22a2
                     contCounter <- contCounter + 1
                 }
ae4c10aa
             }
         }
b26d22a2
         return(annotationColors)
ae4c10aa
     }
 
b26d22a2
 
9c6ba642
 .findGaps <- function(tree, cutreeN) {
b26d22a2
     v <- stats::cutree(tree, cutreeN)[tree$order]
     gaps <- which((v[-1] - v[-length(v)]) != 0)
501d7a5b
     return(gaps)
ae4c10aa
 }
 
9c6ba642
 .is.na2 <- function(x) {
b26d22a2
     if (is.list(x) | length(x) > 1) {
ae4c10aa
         return(FALSE)
     }
b26d22a2
     if (length(x) == 0) {
ae4c10aa
         return(TRUE)
     }
b26d22a2
 
ae4c10aa
     return(is.na(x))
 }
 
9c6ba642
 .identity2 <- function(x, ...) {
ae4c10aa
     return(x)
 }
 
ca5fb59d
 #' @title A function to draw clustered heatmaps.
 #' @description A function to draw clustered heatmaps where one has better
 #'  control over some graphical parameters such as cell size, etc.
ae4c10aa
 #'
ca5fb59d
 #' The function also allows to aggregate the rows using kmeans clustering.
 #'  This is advisable if number of rows is so big that R cannot handle their
 #'  hierarchical clustering anymore, roughly more than 1000. Instead of showing
 #'  all the rows separately one can cluster the rows in advance and show only
 #'  the cluster centers. The number of clusters can be tuned with parameter
 #'  kmeansK.
ae4c10aa
 #' @param mat numeric matrix of the values to be plotted.
 #' @param color vector of colors used in heatmap.
ca5fb59d
 #' @param kmeansK the number of kmeans clusters to make, if we want to
 #'  agggregate the rows before drawing heatmap. If NA then the rows are not
 #'  aggregated.
 #' @param breaks Numeric vector. A sequence of numbers that covers the range
 #'  of values in the normalized `counts`. Values in the normalized `matrix` are
 #'  assigned to each bin in `breaks`. Each break is assigned to a unique color
 #'  from `col`. If NULL, then breaks are calculated automatically. Default NULL.
 #' @param borderColor color of cell borders on heatmap, use NA if no border
 #'  should be drawn.
 #' @param cellWidth individual cell width in points. If left as NA, then the
 #'  values depend on the size of plotting window.
 #' @param cellHeight individual cell height in points. If left as NA, then the
 #'  values depend on the size of plotting window.
 #' @param scale character indicating if the values should be centered and
 #'  scaled in either the row direction or the column direction, or none.
 #'  Corresponding values are \code{"row"}, \code{"column"} and \code{"none"}.
 #' @param clusterRows boolean values determining if rows should be clustered or
 #'  \code{hclust} object,
 #' @param clusterCols boolean values determining if columns should be clustered
 #'  or \code{hclust} object.
 #' @param clusteringDistanceRows distance measure used in clustering rows.
 #'  Possible values are \code{"correlation"} for Pearson correlation and all
 #'  the distances supported by \code{\link{dist}}, such as \code{"euclidean"},
 #'  etc. If the value is none of the above it is assumed that a distance matrix
 #'  is provided.
 #' @param clusteringDistanceCols distance measure used in clustering columns.
 #'  Possible values the same as for clusteringDistanceRows.
b26d22a2
 #' @param clusteringMethod clustering method used. Accepts the same values as
ca5fb59d
 #'  \code{\link{hclust}}.
b26d22a2
 #' @param clusteringCallback callback function to modify the clustering. Is
ca5fb59d
 #'  called with two parameters: original \code{hclust} object and the matrix
 #'  used for clustering. Must return a \code{hclust} object.
b26d22a2
 #' @param cutreeRows number of clusters the rows are divided into, based on the
 #'  hierarchical clustering (using cutree), if rows are not clustered, the
ca5fb59d
 #'  argument is ignored
b26d22a2
 #' @param cutreeCols similar to \code{cutreeRows}, but for columns
 #' @param treeHeightRow the height of a tree for rows, if these are clustered.
ca5fb59d
 #'  Default value 50 points.
 #' @param treeHeightCol the height of a tree for columns, if these are
 #'  clustered. Default value 50 points.
ae4c10aa
 #' @param legend logical to determine if legend should be drawn or not.
b26d22a2
 #' @param legendBreaks vector of breakpoints for the legend.
 #' @param legendLabels vector of labels for the \code{legendBreaks}.
 #' @param annotationRow data frame that specifies the annotations shown on left
 #'  side of the heatmap. Each row defines the features for a specific row. The
ca5fb59d
 #'  rows in the data and in the annotation are matched using corresponding row
ae4c10aa
 #'  names. Note that color schemes takes into account if variable is continuous
 #'  or discrete.
b26d22a2
 #' @param annotationCol similar to annotationRow, but for columns.
ca5fb59d
 #' @param annotation deprecated parameter that currently sets the annotationCol
 #'  if it is missing.
b26d22a2
 #' @param annotationColors list for specifying annotationRow and
ca5fb59d
 #'  annotationCol track colors manually. It is  possible to define the colors
 #'  for only some of the features. Check examples for  details.
b26d22a2
 #' @param annotationLegend boolean value showing if the legend for annotation
ca5fb59d
 #'  tracks should be drawn.
 #' @param annotationNamesRow boolean value showing if the names for row
 #'  annotation tracks should be drawn.
 #' @param annotationNamesCol boolean value showing if the names for column
 #'  annotation tracks should be drawn.
b26d22a2
 #' @param dropLevels logical to determine if unused levels are also shown in
ca5fb59d
 #'  the legend.
b26d22a2
 #' @param showRownames boolean specifying if column names are be shown.
 #' @param showColnames boolean specifying if column names are be shown.
ae4c10aa
 #' @param main the title of the plot
b26d22a2
 #' @param fontSize base fontsize for the plot
 #' @param fontSizeRow fontsize for rownames (Default: fontsize)
 #' @param fontSizeCol fontsize for colnames (Default: fontsize)
ca5fb59d
 #' @param displayNumbers logical determining if the numeric values are also
 #'  printed to the cells. If this is a matrix (with same dimensions as original
 #'  matrix), the contents of the matrix are shown instead of original values.
 #' @param numberFormat format strings (C printf style) of the numbers shown in
 #'  cells. For example "\code{\%.2f}" shows 2 decimal places and "\code{\%.1e}"
 #'  shows exponential notation (see more in \code{\link{sprintf}}).
b26d22a2
 #' @param numberColor color of the text
 #' @param fontSizeNumber fontsize of the numbers displayed in cells
 #' @param gapsRow vector of row indices that show shere to put gaps into
 #'  heatmap. Used only if the rows are not clustered. See \code{cutreeRow}
 #'  to see how to introduce gaps to clustered rows.
 #' @param gapsCol similar to gapsRow, but for columns.
 #' @param labelsRow custom labels for rows that are used instead of rownames.
 #' @param labelsCol similar to labelsRow, but for columns.
 #' @param fileName file path where to save the picture. Filetype is decided by
ca5fb59d
 #'  the extension in the path. Currently following formats are supported: png,
 #'  pdf, tiff, bmp, jpeg. Even if the plot does not fit into the plotting
 #'  window, the file size is calculated so that the plot would fit there,
 #'  unless specified otherwise.
ae4c10aa
 #' @param width manual option for determining the output file width in inches.
 #' @param height manual option for determining the output file height in inches.
 #' @param silent do not draw the plot (useful when using the gtable output)
b26d22a2
 #' @param rowLabel row cluster labels for semi-clustering
 #' @param colLabel column cluster labels for semi-clustering
ca5fb59d
 #' @param \dots graphical parameters for the text used in plot. Parameters
 #'  passed to \code{\link{grid.text}}, see \code{\link{gpar}}.
b26d22a2
 #' @return
 #' Invisibly a list of components
ae4c10aa
 #' \itemize{
ca5fb59d
 #'     \item \code{treeRow} the clustering of rows as \code{\link{hclust}}
 #'       object
 #'     \item \code{treeCol} the clustering of columns as \code{\link{hclust}}
 #'       object
 #'     \item \code{kmeans} the kmeans clustering of rows if parameter
 #'       \code{kmeansK} was specified
ae4c10aa
 #' }
 #' @author  Raivo Kolde <rkolde@@gmail.com>
 #' #@examples
 #' # Create test matrix
 #' test = matrix(rnorm(200), 20, 10)
ca5fb59d
 #' test[seq(10), seq(1, 10, 2)] = test[seq(10), seq(1, 10, 2)] + 3
 #' test[seq(11, 20), seq(2, 10, 2)] = test[seq(11, 20), seq(2, 10, 2)] + 2
 #' test[seq(15, 20), seq(2, 10, 2)] = test[seq(15, 20), seq(2, 10, 2)] + 4
92ca710a
 #' colnames(test) = paste("Test", seq(10), sep = "")
 #' rownames(test) = paste("Gene", seq(20), sep = "")
b26d22a2
 #'
ae4c10aa
 #' # Draw heatmaps
 #' pheatmap(test)
b26d22a2
 #' pheatmap(test, kmeansK = 2)
 #' pheatmap(test, scale = "row", clusteringDistanceRows = "correlation")
ca5fb59d
 #' pheatmap(test, color = colorRampPalette(c("navy",
 #'     "white", "firebrick3"))(50))
ae4c10aa
 #' pheatmap(test, cluster_row = FALSE)
 #' pheatmap(test, legend = FALSE)
b26d22a2
 #'
ae4c10aa
 #' # Show text within cells
b26d22a2
 #' pheatmap(test, displayNumbers = TRUE)
 #' pheatmap(test, displayNumbers = TRUE, numberFormat = "\%.1e")
ca5fb59d
 #' pheatmap(test, displayNumbers = matrix(ifelse(test > 5,
 #'     "*", ""), nrow(test)))
 #' pheatmap(test, cluster_row = FALSE,
 #'     legendBreaks = seq(-1, 4), legendLabels = c("0",
 #'     "1e-4", "1e-3", "1e-2", "1e-1", "1"))
b26d22a2
 #'
ae4c10aa
 #' # Fix cell sizes and save to file with correct size
b26d22a2
 #' pheatmap(test, cellWidth = 15, cellHeight = 12, main = "Example heatmap")
ca5fb59d
 #' pheatmap(test, cellWidth = 15, cellHeight = 12, fontSize = 8,
 #'     fileName = "test.pdf")
b26d22a2
 #'
ae4c10aa
 #' # Generate annotations for rows and columns
ca5fb59d
 #' annotationCol = data.frame(CellType = factor(rep(c("CT1", "CT2"), 5)),
 #'     Time = seq(5))
 #' rownames(annotationCol) = paste("Test", seq(10), sep = "")
b26d22a2
 #'
 #' annotationRow = data.frame(GeneClass = factor(rep(c("Path1",
ca5fb59d
 #'    "Path2",
 #'    "Path3"),
 #'    c(10, 4, 6))))
 #' rownames(annotationRow) = paste("Gene", seq(20), sep = "")
b26d22a2
 #'
ae4c10aa
 #' # Display row and color annotations
b26d22a2
 #' pheatmap(test, annotationCol = annotationCol)
 #' pheatmap(test, annotationCol = annotationCol, annotationLegend = FALSE)
 #' pheatmap(test, annotationCol = annotationCol, annotationRow = annotationRow)
 #'
ae4c10aa
 #' # Specify colors
b26d22a2
 #' ann_colors = list(Time = c("white", "firebrick"),
ae4c10aa
 #'     CellType = c(CT1 = "#1B9E77", CT2 = "#D95F02"),
b26d22a2
 #'     GeneClass = c(Path1 = "#7570B3", Path2 = "#E7298A", Path3 = "#66A61E"))
 #'
ca5fb59d
 #' pheatmap(test, annotationCol = annotationCol, annotationColors = ann_colors,
 #'     main = "Title")
b26d22a2
 #' pheatmap(test, annotationCol = annotationCol, annotationRow = annotationRow,
ca5fb59d
 #'     annotationColors = ann_colors)
 #' pheatmap(test, annotationCol = annotationCol,
 #'     annotationColors = ann_colors[2])
b26d22a2
 #'
ae4c10aa
 #' # Gaps in heatmaps
ca5fb59d
 #' pheatmap(test, annotationCol = annotationCol, clusterRows = FALSE,
 #'     gapsRow = c(10, 14))
 #' pheatmap(test, annotationCol = annotationCol, clusterRows = FALSE,
 #'     gapsRow = c(10, 14), cutreeCol = 2)
b26d22a2
 #'
ae4c10aa
 #' # Show custom strings as row/col names
b26d22a2
 #' labelsRow = c("", "", "", "", "", "", "", "", "", "", "", "", "", "", "",
ae4c10aa
 #' "", "", "Il10", "Il15", "Il1b")
b26d22a2
 #'
 #' pheatmap(test, annotationCol = annotationCol, labelsRow = labelsRow)
 #'
ae4c10aa
 #' # Specifying clustering from distance matrix
 #' drows = stats::dist(test, method = "minkowski")
 #' dcols = stats::dist(t(test), method = "minkowski")
b26d22a2
 #' pheatmap(test,
 #'     clusteringDistanceRows = drows,
 #'     clusteringDistanceCols = dcols)
 #'
ae4c10aa
 #' # Modify ordering of the clusters using clustering callback option
 #' callback = function(hc, mat){
ca5fb59d
 #'     sv = svd(t(mat))$v[, 1]
ae4c10aa
 #'     dend = reorder(as.dendrogram(hc), wts = sv)
 #'     as.hclust(dend)
 #' }
b26d22a2
 #'
 #' pheatmap(test, clusteringCallback = callback)
7890fdf1
 #' @importFrom grid grid.pretty
d7196f24
 #' @importFrom RColorBrewer brewer.pal
b26d22a2
 semiPheatmap <- function(mat,
     color = colorRampPalette(rev(brewer.pal(n = 7, name = "RdYlBu")))(100),
     kmeansK = NA,
     breaks = NA,
     borderColor = "grey60",
     cellWidth = NA,
     cellHeight = NA,
     scale = "none",
     clusterRows = TRUE,
     clusterCols = TRUE,
     clusteringDistanceRows = "euclidean",
     clusteringDistanceCols = "euclidean",
     clusteringMethod = "complete",
9c6ba642
     clusteringCallback = .identity2,
b26d22a2
     cutreeRows = NA,
     cutreeCols = NA,
     treeHeightRow = ifelse(clusterRows, 50, 0),
     treeHeightCol = ifelse(clusterCols, 50, 0),
     legend = TRUE,
     legendBreaks = NA,
     legendLabels = NA,
     annotationRow = NA,
     annotationCol = NA,
     annotation = NA,
     annotationColors = NA,
     annotationLegend = TRUE,
     annotationNamesRow = TRUE,
     annotationNamesCol = TRUE,
     dropLevels = TRUE,
     showRownames = TRUE,
     showColnames = TRUE,
     main = NA,
     fontSize = 10,
     fontSizeRow = fontSize,
     fontSizeCol = fontSize,
     displayNumbers = FALSE,
     numberFormat = "%.2f",
     numberColor = "grey30",
     fontSizeNumber = 0.8 * fontSize,
     gapsRow = NULL,
     gapsCol = NULL,
     labelsRow = NULL,
     labelsCol = NULL,
     fileName = NA,
     width = NA,
     height = NA,
     silent = FALSE,
     rowLabel,
     colLabel,
     ...) {
 
ae4c10aa
     # Set labels
b26d22a2
     if (is.null(labelsRow) & !is.null(rownames(mat))) {
         labelsRow <- rownames(mat)
ae4c10aa
     }
b26d22a2
     if (is.null(labelsRow) & is.null(rownames(mat))) {
22ad839c
         labelsRow <- seq(nrow(mat))
         rownames(mat) <- seq(nrow(mat))
ae4c10aa
     }
 
b26d22a2
     if (is.null(labelsCol) & !is.null(colnames(mat))) {
         labelsCol <- colnames(mat)
ae4c10aa
     }
b26d22a2
     if (is.null(labelsCol) & is.null(colnames(mat))) {
22ad839c
         labelsCol <- seq(ncol(mat))
         colnames(mat) <- seq(ncol(mat))
ae4c10aa
     }
 
b26d22a2
 
9c6ba642
     if (.is.na2(breaks)) {
         breaks <- .generateBreaks(mat, length(color), center = TRUE)
ae4c10aa
     }
b26d22a2
 
 
ae4c10aa
     # Kmeans
b26d22a2
     if (!is.na(kmeansK)) {
ae4c10aa
         # Cluster data
b26d22a2
         km <- stats::kmeans(mat, kmeansK, iter.max = 100)
         mat <- km$centers
 
ae4c10aa
         # Compose rownames
b26d22a2
         t <- table(km$cluster)
         labelsRow <- sprintf("Cluster: %s Size: %d", names(t), t)
     } else {
         km <- NA
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     # Format numbers to be displayed in cells
b26d22a2
     if (is.matrix(displayNumbers) | is.data.frame(displayNumbers)) {
         if (nrow(displayNumbers) != nrow(mat) |
                 ncol(displayNumbers) != ncol(mat)) {
             stop("If displayNumbers provided as matrix,
                 its dimensions have to match with mat")
ae4c10aa
         }
b26d22a2
 
         displayNumbers <- as.matrix(displayNumbers)
         fmat <- matrix(as.character(displayNumbers),
                     nrow = nrow(displayNumbers),
                     ncol = ncol(displayNumbers))
         fmatDraw <- TRUE
     } else {
         if (displayNumbers) {
             fmat <- matrix(sprintf(numberFormat, mat),
                     nrow = nrow(mat),
                     ncol = ncol(mat))
             fmatDraw <- TRUE
         } else {
             fmat <- matrix(NA, nrow = nrow(mat), ncol = ncol(mat))
             fmatDraw <- FALSE
ae4c10aa
         }
     }
 
     # Do clustering for rows
b26d22a2
     if (clusterRows == TRUE) {
         if (is.null(rowLabel)) {
             rowLabel <- rep(1, nrow(mat))
         } else {
             o <- order(rowLabel)
             mat <- mat[o, , drop = FALSE]
             fmat <- fmat[o, , drop = FALSE]
             rowLabel <- rowLabel[o]
             if (!is.null(annotationRow)) {
                 annotationRow <- annotationRow[o, , drop = FALSE]
             }
         }
 
9c6ba642
         treeRow <- .clusterMat(mat,
b26d22a2
             rowLabel,
             distance = clusteringDistanceRows,
             method = clusteringMethod)
         treeRow <- clusteringCallback(treeRow, mat)
 
         mat <- mat[treeRow$order, , drop = FALSE]
         fmat <- fmat[treeRow$order, , drop = FALSE]
         labelsRow <- labelsRow[treeRow$order]
         if (!is.na(cutreeRows)) {
9c6ba642
             gapsRow <- .findGaps(treeRow, cutreeRows)
b26d22a2
         } else {
             gapsRow <- NULL
         }
ae4c10aa
     } else {
b26d22a2
         treeRow <- NA
         treeHeightRow <- 0
     }
 
 
ae4c10aa
     ## Do clustering for columns
b26d22a2
     if (clusterCols == TRUE) {
         if (is.null(colLabel)) {
             colLabel <- rep(1, ncol(mat))
         } else {
             o <- order(colLabel)
             mat <- mat[, o, drop = FALSE]
             fmat <- fmat[, o, drop = FALSE]
             colLabel <- colLabel[o]
             if (!is.null(annotationCol)) {
                 annotationCol <- annotationCol[o, , drop = FALSE]
             }
         }
 
9c6ba642
         treeCol <- .clusterMat(t(mat),
b26d22a2
             colLabel,
             distance = clusteringDistanceCols,
             method = clusteringMethod)
         treeCol <- clusteringCallback(treeCol, t(mat))
 
         mat <- mat[, treeCol$order, drop = FALSE]
         fmat <- fmat[, treeCol$order, drop = FALSE]
         labelsCol <- labelsCol[treeCol$order]
 
         if (!is.na(cutreeCols)) {
9c6ba642
             gapsCol <- .findGaps(treeCol, cutreeCols)
b26d22a2
         } else {
             gapsCol <- NULL
         }
ae4c10aa
     } else {
b26d22a2
         treeCol <- NA
         treeHeightCol <- 0
     }
 
     attr(fmat, "draw") <- fmatDraw
 
ae4c10aa
     # Colors and scales
9c6ba642
     if (!.is.na2(legendBreaks) & !.is.na2(legendLabels)) {
b26d22a2
         if (length(legendBreaks) != length(legendLabels)) {
             stop("Lengths of legendBreaks and legendLabels must be the same")
ae4c10aa
         }
     }
b26d22a2
 
 
9c6ba642
     if (.is.na2(breaks)) {
         breaks <- .generateBreaks(as.vector(mat), length(color))
ae4c10aa
     }
9c6ba642
     if (legend & .is.na2(legendBreaks)) {
7890fdf1
         legend <- grid::grid.pretty(range(as.vector(breaks)))
b26d22a2
         names(legend) <- legend
ae4c10aa
     }
9c6ba642
     else if (legend & !.is.na2(legendBreaks)) {
b26d22a2
         legend <- legendBreaks[legendBreaks >= min(breaks) &
                 legendBreaks <= max(breaks)]
 
9c6ba642
         if (!.is.na2(legendLabels)) {
b26d22a2
             legendLabels <- legendLabels[legendBreaks >= min(breaks) &
                     legendBreaks <= max(breaks)]
             names(legend) <- legendLabels
         } else {
             names(legend) <- legend
ae4c10aa
         }
b26d22a2
     } else {
         legend <- NA
ae4c10aa
     }
9c6ba642
     mat <- .scaleColours(mat, col = color, breaks = breaks)
b26d22a2
 
     annotation <- c(annotationRow, annotationCol)
     annotation <- annotation[unlist(lapply(annotation,
9c6ba642
         function(x) !.is.na2(x)))]
b26d22a2
     if (length(annotation) != 0) {
2c8e7d4d
         annotationColors <- .generateAnnotationColours(annotation,
b26d22a2
             annotationColors,
             drop = dropLevels)
     } else {
         annotationColors <- NA
ae4c10aa
     }
b26d22a2
 
     labelsRow <- rownames(mat)
     labelsCol <- colnames(mat)
 
     if (!showRownames) {
         labelsRow <- NULL
ae4c10aa
     }
b26d22a2
 
     if (!showColnames) {
         labelsCol <- NULL
ae4c10aa
     }
b26d22a2
 
ae4c10aa
     # Draw heatmap
b26d22a2
     gt <- .heatmapMotor(mat,
         borderColor = borderColor,
         cellWidth = cellWidth,
         cellHeight = cellHeight,
         treeHeightCol = treeHeightCol,
         treeHeightRow = treeHeightRow,
         treeCol = treeCol,
         treeRow = treeRow,
         fileName = fileName,
         width = width,
         height = height,
         breaks = breaks,
         color = color,
         legend = legend,
         annotationRow = annotationRow,
         annotationCol = annotationCol,
         annotationColors = annotationColors,
         annotationLegend = annotationLegend,
         annotationNamesRow = annotationNamesRow,
         annotationNamesCol = annotationNamesCol,
         main = main,
         fontSize = fontSize,
         fontSizeRow = fontSizeRow,
         fontSizeCol = fontSizeCol,
         fmat = fmat,
         fontSizeNumber = fontSizeNumber,
         numberColor = numberColor,
         gapsRow = gapsRow,
         gapsCol = gapsCol,
         labelsRow = labelsRow,
         labelsCol = labelsCol,
         ...)
 
     if (is.na(fileName) & !silent) {
ae4c10aa
         grid.newpage()
         grid.draw(gt)
     }
 
b26d22a2
     invisible(list(treeRow = treeRow,
         treeCol = treeCol,
         gtable = gt))
 }