Browse code

multiple moduleHeatmap on same page. remove blank page

zhewa authored on 16/09/2020 15:50:01
Showing 1 changed files
... ...
@@ -1973,16 +1973,7 @@ semiPheatmap <- function(mat,
1973 1973
     ...
1974 1974
   )
1975 1975
 
1976
-  if (is.na(fileName) & !silent) {
1977
-    grid.newpage()
1978
-    grid.draw(gt)
1979
-  }
1980
-
1981
-  return(list(
1982
-    treeRow = treeRow,
1983
-    treeCol = treeCol,
1984
-    gtable = gt
1985
-  ))
1976
+  return(gt)
1986 1977
 }
1987 1978
 
1988 1979
 
Browse code

Ran styler and fixed lints

Joshua D. Campbell authored on 06/04/2020 23:58:56
Showing 1 changed files
... ...
@@ -3,583 +3,660 @@
3 3
 
4 4
 #' @importFrom gtable gtable
5 5
 .lo <- function(rown,
6
-    coln,
7
-    nrow,
8
-    ncol,
9
-    cellHeight = NA,
10
-    cellWidth = NA,
11
-    treeHeightCol,
12
-    treeHeightRow,
13
-    legend,
14
-    annotationRow,
15
-    annotationCol,
16
-    annotationColors,
17
-    annotationLegend,
18
-    annotationNamesRow,
19
-    annotationNamesCol,
20
-    main,
21
-    fontSize,
22
-    fontSizeRow,
23
-    fontSizeCol,
24
-    gapsRow,
25
-    gapsCol,
26
-    ...) {
27
-    # Get height of colnames and length of rownames
28
-    if (!is.null(coln[1]) |
29
-            (!.is.na2(annotationRow) & annotationNamesRow)) {
30
-        if (!is.null(coln[1])) {
31
-            t <- coln
32
-        } else {
33
-            t <- ""
34
-        }
35
-        tw <- strwidth(t, units = "in", cex = fontSizeCol / fontSize)
36
-        if (annotationNamesRow) {
37
-            t <- c(t, colnames(annotationRow))
38
-            tw <- c(tw, strwidth(colnames(annotationRow), units = "in"))
39
-        }
40
-        longestColn <- which.max(tw)
41
-        gp <- list(fontSize = ifelse(longestColn <= length(coln),
42
-            fontSizeCol,
43
-            fontSize), ...)
44
-        colnHeight <- unit(1,
45
-            "grobheight",
46
-            textGrob(t[longestColn],
47
-                rot = 90,
48
-                gp = do.call(gpar, gp))) +
49
-            unit(10, "bigpts")
50
-    } else {
51
-        colnHeight <- unit(5, "bigpts")
52
-    }
53
-
54
-    if (!is.null(rown[1])) {
55
-        t <- rown
56
-        tw <- strwidth(t, units = "in", cex = fontSizeRow / fontSize)
57
-        if (annotationNamesCol) {
58
-            t <- c(t, colnames(annotationCol))
59
-            tw <- c(tw, strwidth(colnames(annotationCol), units = "in"))
60
-        }
61
-        longestRown <- which.max(tw)
62
-        gp <- list(fontSize = ifelse(longestRown <= length(rown),
63
-            fontSizeRow,
64
-            fontSize), ...)
65
-        rownWidth <- unit(1,
66
-            "grobwidth",
67
-            textGrob(t[longestRown],
68
-                gp = do.call(gpar, gp))) +
69
-            unit(10, "bigpts")
70
-    } else {
71
-        rownWidth <- unit(5, "bigpts")
72
-    }
73
-
74
-    gp <- list(fontSize = fontSize, ...)
75
-    # Legend position
76
-    if (!.is.na2(legend)) {
77
-        longestBreak <- which.max(nchar(names(legend)))
78
-        longestBreak <- unit(1.1,
79
-                "grobwidth",
80
-                textGrob(as.character(names(legend))[longestBreak],
81
-                    gp = do.call(gpar, gp)))
82
-        titleLength <- unit(1.1,
83
-            "grobwidth",
84
-            textGrob("Scale",
85
-                gp = gpar(fontface = "bold",
86
-                    ...)))
87
-        legendWidth <- unit(12, "bigpts") + longestBreak * 1.2
88
-        legendWidth <- max(titleLength, legendWidth)
89
-    } else {
90
-        legendWidth <- unit(0, "bigpts")
91
-    }
92
-
93
-    # Set main title height
94
-    if (is.na(main)) {
95
-        mainHeight <- unit(0, "npc")
6
+                coln,
7
+                nrow,
8
+                ncol,
9
+                cellHeight = NA,
10
+                cellWidth = NA,
11
+                treeHeightCol,
12
+                treeHeightRow,
13
+                legend,
14
+                annotationRow,
15
+                annotationCol,
16
+                annotationColors,
17
+                annotationLegend,
18
+                annotationNamesRow,
19
+                annotationNamesCol,
20
+                main,
21
+                fontSize,
22
+                fontSizeRow,
23
+                fontSizeCol,
24
+                gapsRow,
25
+                gapsCol,
26
+                ...) {
27
+  # Get height of colnames and length of rownames
28
+  if (!is.null(coln[1]) |
29
+    (!.is.na2(annotationRow) & annotationNamesRow)) {
30
+    if (!is.null(coln[1])) {
31
+      t <- coln
96 32
     } else {
97
-        mainHeight <- unit(1.5,
98
-            "grobheight",
99
-            textGrob(main,
100
-                gp = gpar(fontSize = 1.3 * fontSize,
101
-                    ...)))
33
+      t <- ""
102 34
     }
103
-
104
-    # Column annotations
105
-    textheight <- unit(fontSize, "bigpts")
106
-
107
-    if (!.is.na2(annotationCol)) {
108
-        # Column annotation height
109
-        annotColHeight <-
110
-            ncol(annotationCol) *
111
-            (textheight + unit(2, "bigpts")) +
112
-            unit(2, "bigpts")
113
-
114
-        # Width of the correponding legend
115
-        t <- c(as.vector(as.matrix(annotationCol)), colnames(annotationCol))
116
-        annotColLegendWidth <- unit(1.2,
117
-            "grobwidth",
118
-            textGrob(t[which.max(nchar(t))],
119
-                gp = gpar(...))) +
120
-            unit(12, "bigpts")
121
-        if (!annotationLegend) {
122
-            annotColLegendWidth <- unit(0, "npc")
123
-        }
124
-    } else {
125
-        annotColHeight <- unit(0, "bigpts")
126
-        annotColLegendWidth <- unit(0, "bigpts")
35
+    tw <- strwidth(t, units = "in", cex = fontSizeCol / fontSize)
36
+    if (annotationNamesRow) {
37
+      t <- c(t, colnames(annotationRow))
38
+      tw <- c(tw, strwidth(colnames(annotationRow), units = "in"))
127 39
     }
128
-
129
-    # Row annotations
130
-    if (!.is.na2(annotationRow)) {
131
-        # Row annotation width
132
-        annotRowWidth <- ncol(annotationRow) *
133
-            (textheight + unit(2, "bigpts")) +
134
-            unit(2, "bigpts")
135
-
136
-        # Width of the correponding legend
137
-        t <- c(as.vector(as.matrix(annotationRow)),
138
-            colnames(annotationRow))
139
-        annotRowLegendWidth <- unit(1.2,
140
-            "grobwidth",
141
-            textGrob(t[which.max(nchar(t))],
142
-                gp = gpar(...))) +
143
-            unit(12,
144
-                "bigpts")
145
-
146
-        if (!annotationLegend) {
147
-            annotRowLegendWidth <- unit(0, "npc")
148
-        }
149
-    } else {
150
-        annotRowWidth <- unit(0, "bigpts")
151
-        annotRowLegendWidth <- unit(0, "bigpts")
40
+    longestColn <- which.max(tw)
41
+    gp <- list(fontSize = ifelse(longestColn <= length(coln),
42
+      fontSizeCol,
43
+      fontSize
44
+    ), ...)
45
+    colnHeight <- unit(
46
+      1,
47
+      "grobheight",
48
+      textGrob(t[longestColn],
49
+        rot = 90,
50
+        gp = do.call(gpar, gp)
51
+      )
52
+    ) +
53
+      unit(10, "bigpts")
54
+  } else {
55
+    colnHeight <- unit(5, "bigpts")
56
+  }
57
+
58
+  if (!is.null(rown[1])) {
59
+    t <- rown
60
+    tw <- strwidth(t, units = "in", cex = fontSizeRow / fontSize)
61
+    if (annotationNamesCol) {
62
+      t <- c(t, colnames(annotationCol))
63
+      tw <- c(tw, strwidth(colnames(annotationCol), units = "in"))
152 64
     }
153
-
154
-    annotLegendWidth <- max(annotRowLegendWidth, annotColLegendWidth)
155
-
156
-    # Tree height
157
-    treeHeightCol <- unit(treeHeightCol, "bigpts") + unit(5, "bigpts")
158
-    treeHeightRow <- unit(treeHeightRow, "bigpts") + unit(5, "bigpts")
159
-
160
-    # Set cell sizes
161
-    if (is.na(cellWidth)) {
162
-        matWidth <- unit(1, "npc") -
163
-            rownWidth -
164
-            legendWidth -
165
-            treeHeightRow -
166
-            annotRowWidth -
167
-            annotLegendWidth
168
-    } else {
169
-        matWidth <- unit(cellWidth * ncol, "bigpts") +
170
-            length(gapsCol) *
171
-            unit(0, "bigpts")
65
+    longestRown <- which.max(tw)
66
+    gp <- list(fontSize = ifelse(longestRown <= length(rown),
67
+      fontSizeRow,
68
+      fontSize
69
+    ), ...)
70
+    rownWidth <- unit(
71
+      1,
72
+      "grobwidth",
73
+      textGrob(t[longestRown],
74
+        gp = do.call(gpar, gp)
75
+      )
76
+    ) +
77
+      unit(10, "bigpts")
78
+  } else {
79
+    rownWidth <- unit(5, "bigpts")
80
+  }
81
+
82
+  gp <- list(fontSize = fontSize, ...)
83
+  # Legend position
84
+  if (!.is.na2(legend)) {
85
+    longestBreak <- which.max(nchar(names(legend)))
86
+    longestBreak <- unit(
87
+      1.1,
88
+      "grobwidth",
89
+      textGrob(as.character(names(legend))[longestBreak],
90
+        gp = do.call(gpar, gp)
91
+      )
92
+    )
93
+    titleLength <- unit(
94
+      1.1,
95
+      "grobwidth",
96
+      textGrob("Scale",
97
+        gp = gpar(
98
+          fontface = "bold",
99
+          ...
100
+        )
101
+      )
102
+    )
103
+    legendWidth <- unit(12, "bigpts") + longestBreak * 1.2
104
+    legendWidth <- max(titleLength, legendWidth)
105
+  } else {
106
+    legendWidth <- unit(0, "bigpts")
107
+  }
108
+
109
+  # Set main title height
110
+  if (is.na(main)) {
111
+    mainHeight <- unit(0, "npc")
112
+  } else {
113
+    mainHeight <- unit(
114
+      1.5,
115
+      "grobheight",
116
+      textGrob(main,
117
+        gp = gpar(
118
+          fontSize = 1.3 * fontSize,
119
+          ...
120
+        )
121
+      )
122
+    )
123
+  }
124
+
125
+  # Column annotations
126
+  textheight <- unit(fontSize, "bigpts")
127
+
128
+  if (!.is.na2(annotationCol)) {
129
+    # Column annotation height
130
+    annotColHeight <-
131
+      ncol(annotationCol) *
132
+      (textheight + unit(2, "bigpts")) +
133
+      unit(2, "bigpts")
134
+
135
+    # Width of the correponding legend
136
+    t <- c(as.vector(as.matrix(annotationCol)), colnames(annotationCol))
137
+    annotColLegendWidth <- unit(
138
+      1.2,
139
+      "grobwidth",
140
+      textGrob(t[which.max(nchar(t))],
141
+        gp = gpar(...)
142
+      )
143
+    ) +
144
+      unit(12, "bigpts")
145
+    if (!annotationLegend) {
146
+      annotColLegendWidth <- unit(0, "npc")
172 147
     }
173
-
174
-    if (is.na(cellHeight)) {
175
-        matHeight <- unit(1, "npc") -
176
-            mainHeight -
177
-            colnHeight -
178
-            treeHeightCol -
179
-            annotColHeight
180
-    } else {
181
-        matHeight <- unit(cellHeight * nrow, "bigpts") +
182
-            length(gapsRow) *
183
-            unit(0, "bigpts")
148
+  } else {
149
+    annotColHeight <- unit(0, "bigpts")
150
+    annotColLegendWidth <- unit(0, "bigpts")
151
+  }
152
+
153
+  # Row annotations
154
+  if (!.is.na2(annotationRow)) {
155
+    # Row annotation width
156
+    annotRowWidth <- ncol(annotationRow) *
157
+      (textheight + unit(2, "bigpts")) +
158
+      unit(2, "bigpts")
159
+
160
+    # Width of the correponding legend
161
+    t <- c(
162
+      as.vector(as.matrix(annotationRow)),
163
+      colnames(annotationRow)
164
+    )
165
+    annotRowLegendWidth <- unit(
166
+      1.2,
167
+      "grobwidth",
168
+      textGrob(t[which.max(nchar(t))],
169
+        gp = gpar(...)
170
+      )
171
+    ) +
172
+      unit(
173
+        12,
174
+        "bigpts"
175
+      )
176
+
177
+    if (!annotationLegend) {
178
+      annotRowLegendWidth <- unit(0, "npc")
184 179
     }
185
-
186
-    # Produce gtable
187
-    gt <- gtable::gtable(widths = unit.c(treeHeightRow,
188
-            annotRowWidth,
189
-            matWidth,
190
-            rownWidth,
191
-            legendWidth,
192
-            annotLegendWidth),
193
-        heights = unit.c(mainHeight,
194
-            treeHeightCol,
195
-            annotColHeight,
196
-            matHeight,
197
-            colnHeight),
198
-        vp = viewport(gp = do.call(gpar, gp)))
199
-
200
-    cw <- convertWidth(matWidth -
201
-        (length(gapsCol) * unit(0, "bigpts")),
202
-        "bigpts", valueOnly = TRUE) / ncol
203
-    ch <- convertHeight(matHeight -
204
-        (length(gapsRow) * unit(0, "bigpts")),
205
-        "bigpts", valueOnly = TRUE) / nrow
206
-
207
-    # Return minimal cell dimension in bigpts to decide if borders are drawn
208
-    mindim <- min(cw, ch)
209
-
210
-    res <- list(gt = gt, mindim = mindim)
211
-
212
-    return(res)
180
+  } else {
181
+    annotRowWidth <- unit(0, "bigpts")
182
+    annotRowLegendWidth <- unit(0, "bigpts")
183
+  }
184
+
185
+  annotLegendWidth <- max(annotRowLegendWidth, annotColLegendWidth)
186
+
187
+  # Tree height
188
+  treeHeightCol <- unit(treeHeightCol, "bigpts") + unit(5, "bigpts")
189
+  treeHeightRow <- unit(treeHeightRow, "bigpts") + unit(5, "bigpts")
190
+
191
+  # Set cell sizes
192
+  if (is.na(cellWidth)) {
193
+    matWidth <- unit(1, "npc") -
194
+      rownWidth -
195
+      legendWidth -
196
+      treeHeightRow -
197
+      annotRowWidth -
198
+      annotLegendWidth
199
+  } else {
200
+    matWidth <- unit(cellWidth * ncol, "bigpts") +
201
+      length(gapsCol) *
202
+        unit(0, "bigpts")
203
+  }
204
+
205
+  if (is.na(cellHeight)) {
206
+    matHeight <- unit(1, "npc") -
207
+      mainHeight -
208
+      colnHeight -
209
+      treeHeightCol -
210
+      annotColHeight
211
+  } else {
212
+    matHeight <- unit(cellHeight * nrow, "bigpts") +
213
+      length(gapsRow) *
214
+        unit(0, "bigpts")
215
+  }
216
+
217
+  # Produce gtable
218
+  gt <- gtable::gtable(
219
+    widths = unit.c(
220
+      treeHeightRow,
221
+      annotRowWidth,
222
+      matWidth,
223
+      rownWidth,
224
+      legendWidth,
225
+      annotLegendWidth
226
+    ),
227
+    heights = unit.c(
228
+      mainHeight,
229
+      treeHeightCol,
230
+      annotColHeight,
231
+      matHeight,
232
+      colnHeight
233
+    ),
234
+    vp = viewport(gp = do.call(gpar, gp))
235
+  )
236
+
237
+  cw <- convertWidth(matWidth -
238
+    (length(gapsCol) * unit(0, "bigpts")),
239
+  "bigpts",
240
+  valueOnly = TRUE
241
+  ) / ncol
242
+  ch <- convertHeight(matHeight -
243
+    (length(gapsRow) * unit(0, "bigpts")),
244
+  "bigpts",
245
+  valueOnly = TRUE
246
+  ) / nrow
247
+
248
+  # Return minimal cell dimension in bigpts to decide if borders are drawn
249
+  mindim <- min(cw, ch)
250
+
251
+  res <- list(gt = gt, mindim = mindim)
252
+
253
+  return(res)
213 254
 }
214 255
 
215 256
 .findCoordinates <- function(n, gaps, m = seq(1, n)) {
216
-    if (length(gaps) == 0) {
217
-        return(list(
218
-            coord = unit(m / n, "npc"),
219
-            size = unit(1 / n, "npc")))
220
-    }
257
+  if (length(gaps) == 0) {
258
+    return(list(
259
+      coord = unit(m / n, "npc"),
260
+      size = unit(1 / n, "npc")
261
+    ))
262
+  }
221 263
 
222
-    if (max(gaps) > n) {
223
-        stop("Gaps do not match with matrix size")
224
-    }
225
-
226
-    size <- (1 / n) *
227
-        (unit(1, "npc") - length(gaps) * unit("0", "bigpts"))
264
+  if (max(gaps) > n) {
265
+    stop("Gaps do not match with matrix size")
266
+  }
228 267
 
229
-    gaps2 <- base::apply(vapply(gaps,
230
-        function(gap, x) {
231
-            x > gap
232
-        },
233
-        integer(n), m), 1, sum)
234
-    coord <- m * size + (gaps2 * unit("0", "bigpts"))
268
+  size <- (1 / n) *
269
+    (unit(1, "npc") - length(gaps) * unit("0", "bigpts"))
235 270
 
236
-    return(list(coord = coord, size = size))
271
+  gaps2 <- base::apply(vapply(
272
+    gaps,
273
+    function(gap, x) {
274
+      x > gap
275
+    },
276
+    integer(n), m
277
+  ), 1, sum)
278
+  coord <- m * size + (gaps2 * unit("0", "bigpts"))
279
+
280
+  return(list(coord = coord, size = size))
237 281
 }
238 282
 
239 283
 .drawDendrogram <- function(hc, gaps, horizontal = TRUE) {
240
-    h <- hc$height / max(hc$height) / 1.05
241
-    m <- hc$merge
242
-    o <- hc$order
243
-    n <- length(o)
244
-
245
-    m[m > 0] <- n + m[m > 0]
246
-    m[m < 0] <- abs(m[m < 0])
247
-
248
-    dist <- matrix(0,
249
-        nrow = 2 * n - 1,
250
-        ncol = 2,
251
-        dimnames = list(NULL, c("x", "y")))
252
-    dist[seq(1, n), 1] <- 1 / n / 2 + (1 / n) *
253
-        (match(seq(1, n), o) - 1)
254
-
255
-    for (i in seq(1, nrow(m))) {
256
-        dist[n + i, 1] <- (dist[m[i, 1], 1] + dist[m[i, 2], 1]) / 2
257
-        dist[n + i, 2] <- h[i]
258
-    }
259
-
260
-    drawConnection <- function(x1, x2, y1, y2, y) {
261
-        res <- list(x = c(x1, x1, x2, x2),
262
-            y = c(y1, y, y, y2))
263
-
264
-        return(res)
265
-    }
266
-
267
-    x <- rep(NA, nrow(m) * 4)
268
-    y <- rep(NA, nrow(m) * 4)
269
-    id <- rep(seq(nrow(m)), rep(4, nrow(m)))
270
-
271
-    for (i in seq(1, nrow(m))) {
272
-        c <- drawConnection(dist[m[i, 1], 1],
273
-            dist[m[i, 2], 1],
274
-            dist[m[i, 1], 2],
275
-            dist[m[i, 2], 2],
276
-            h[i])
277
-        k <- (i - 1) * 4 + 1
278
-        x[seq(k, k + 3)] <- c$x
279
-        y[seq(k, k + 3)] <- c$y
280
-    }
281
-
282
-    x <- .findCoordinates(n, gaps, x * n)$coord
283
-    y <- unit(y, "npc")
284
-
285
-    if (!horizontal) {
286
-        a <- x
287
-        x <- unit(1, "npc") - y
288
-        y <- unit(1, "npc") - a
289
-    }
290
-    res <- polylineGrob(x = x, y = y, id = id)
284
+  h <- hc$height / max(hc$height) / 1.05
285
+  m <- hc$merge
286
+  o <- hc$order
287
+  n <- length(o)
288
+
289
+  m[m > 0] <- n + m[m > 0]
290
+  m[m < 0] <- abs(m[m < 0])
291
+
292
+  dist <- matrix(0,
293
+    nrow = 2 * n - 1,
294
+    ncol = 2,
295
+    dimnames = list(NULL, c("x", "y"))
296
+  )
297
+  dist[seq(1, n), 1] <- 1 / n / 2 + (1 / n) *
298
+    (match(seq(1, n), o) - 1)
299
+
300
+  for (i in seq(1, nrow(m))) {
301
+    dist[n + i, 1] <- (dist[m[i, 1], 1] + dist[m[i, 2], 1]) / 2
302
+    dist[n + i, 2] <- h[i]
303
+  }
304
+
305
+  drawConnection <- function(x1, x2, y1, y2, y) {
306
+    res <- list(
307
+      x = c(x1, x1, x2, x2),
308
+      y = c(y1, y, y, y2)
309
+    )
291 310
 
292 311
     return(res)
312
+  }
313
+
314
+  x <- rep(NA, nrow(m) * 4)
315
+  y <- rep(NA, nrow(m) * 4)
316
+  id <- rep(seq(nrow(m)), rep(4, nrow(m)))
317
+
318
+  for (i in seq(1, nrow(m))) {
319
+    c <- drawConnection(
320
+      dist[m[i, 1], 1],
321
+      dist[m[i, 2], 1],
322
+      dist[m[i, 1], 2],
323
+      dist[m[i, 2], 2],
324
+      h[i]
325
+    )
326
+    k <- (i - 1) * 4 + 1
327
+    x[seq(k, k + 3)] <- c$x
328
+    y[seq(k, k + 3)] <- c$y
329
+  }
330
+
331
+  x <- .findCoordinates(n, gaps, x * n)$coord
332
+  y <- unit(y, "npc")
333
+
334
+  if (!horizontal) {
335
+    a <- x
336
+    x <- unit(1, "npc") - y
337
+    y <- unit(1, "npc") - a
338
+  }
339
+  res <- polylineGrob(x = x, y = y, id = id)
340
+
341
+  return(res)
293 342
 }
294 343
 
295 344
 .drawMatrix <- function(matrix,
296
-    borderColor,
297
-    gapsRows,
298
-    gapsCols,
299
-    fmat,
300
-    fontSizeNumber,
301
-    numberColor) {
302
-
303
-    n <- nrow(matrix)
304
-    m <- ncol(matrix)
305
-
306
-    coordX <- .findCoordinates(m, gapsCols)
307
-    coordY <- .findCoordinates(n, gapsRows)
308
-
309
-    x <- coordX$coord -
310
-        0.5 * coordX$size
311
-    y <- unit(1, "npc") -
312
-        (coordY$coord - 0.5 * coordY$size)
313
-
314
-    coord <- expand.grid(y = y, x = x)
315
-
316
-    res <- gList()
317
-
318
-    res[["rect"]] <- rectGrob(x = coord$x,
319
-        y = coord$y,
320
-        width = coordX$size,
321
-        height = coordY$size,
322
-        gp = gpar(fill = matrix, col = borderColor))
323
-
324
-    if (attr(fmat, "draw")) {
325
-        res[["text"]] <- textGrob(x = coord$x,
326
-            y = coord$y,
327
-            label = fmat,
328
-            gp = gpar(col = numberColor, fontSize = fontSizeNumber))
329
-    }
330
-
331
-    res <- gTree(children = res)
332
-
333
-    return(res)
345
+                        borderColor,
346
+                        gapsRows,
347
+                        gapsCols,
348
+                        fmat,
349
+                        fontSizeNumber,
350
+                        numberColor) {
351
+  n <- nrow(matrix)
352
+  m <- ncol(matrix)
353
+
354
+  coordX <- .findCoordinates(m, gapsCols)
355
+  coordY <- .findCoordinates(n, gapsRows)
356
+
357
+  x <- coordX$coord -
358
+    0.5 * coordX$size
359
+  y <- unit(1, "npc") -
360
+    (coordY$coord - 0.5 * coordY$size)
361
+
362
+  coord <- expand.grid(y = y, x = x)
363
+
364
+  res <- gList()
365
+
366
+  res[["rect"]] <- rectGrob(
367
+    x = coord$x,
368
+    y = coord$y,
369
+    width = coordX$size,
370
+    height = coordY$size,
371
+    gp = gpar(fill = matrix, col = borderColor)
372
+  )
373
+
374
+  if (attr(fmat, "draw")) {
375
+    res[["text"]] <- textGrob(
376
+      x = coord$x,
377
+      y = coord$y,
378
+      label = fmat,
379
+      gp = gpar(col = numberColor, fontSize = fontSizeNumber)
380
+    )
381
+  }
382
+
383
+  res <- gTree(children = res)
384
+
385
+  return(res)
334 386
 }
335 387
 
336 388
 .drawColnames <- function(coln, gaps, ...) {
337
-    coord <- .findCoordinates(length(coln), gaps)
338
-    x <- coord$coord - 0.5 * coord$size
339
-
340
-    res <- textGrob(coln,
341
-        x = x,
342
-        y = unit(1, "npc") -
343
-            unit(3, "bigpts"),
344
-        vjust = 0.5,
345
-        hjust = 0,
346
-        rot = 270,
347
-        gp = gpar(...))
348
-
349
-    return(res)
389
+  coord <- .findCoordinates(length(coln), gaps)
390
+  x <- coord$coord - 0.5 * coord$size
391
+
392
+  res <- textGrob(coln,
393
+    x = x,
394
+    y = unit(1, "npc") -
395
+      unit(3, "bigpts"),
396
+    vjust = 0.5,
397
+    hjust = 0,
398
+    rot = 270,
399
+    gp = gpar(...)
400
+  )
401
+
402
+  return(res)
350 403
 }
351 404
 
352 405
 .drawRownames <- function(rown, gaps, ...) {
353
-    coord <- .findCoordinates(length(rown), gaps)
354
-    y <- unit(1, "npc") - (coord$coord - 0.5 * coord$size)
355
-
356
-    res <- textGrob(rown,
357
-            x = unit(3, "bigpts"),
358
-            y = y,
359
-            vjust = 0.5,
360
-            hjust = 0,
361
-            gp = gpar(...))
362
-
363
-    return(res)
406
+  coord <- .findCoordinates(length(rown), gaps)
407
+  y <- unit(1, "npc") - (coord$coord - 0.5 * coord$size)
408
+
409
+  res <- textGrob(rown,
410
+    x = unit(3, "bigpts"),
411
+    y = y,
412
+    vjust = 0.5,
413
+    hjust = 0,
414
+    gp = gpar(...)
415
+  )
416
+
417
+  return(res)
364 418
 }
365 419
 
366 420
 .drawLegend <- function(color, breaks, legend, ...) {
367
-    height <- min(unit(1, "npc"), unit(150, "bigpts"))
421
+  height <- min(unit(1, "npc"), unit(150, "bigpts"))
368 422
 
369
-    legendPos <- (legend - min(breaks)) / (max(breaks) - min(breaks))
370
-    legendPos <- height * legendPos + (unit(1, "npc") - height)
423
+  legendPos <- (legend - min(breaks)) / (max(breaks) - min(breaks))
424
+  legendPos <- height * legendPos + (unit(1, "npc") - height)
371 425
 
372
-    breaks <- (breaks - min(breaks)) / (max(breaks) - min(breaks))
373
-    breaks <- height * breaks + (unit(1, "npc") - height)
426
+  breaks <- (breaks - min(breaks)) / (max(breaks) - min(breaks))
427
+  breaks <- height * breaks + (unit(1, "npc") - height)
374 428
 
375
-    h <- breaks[-1] - breaks[-length(breaks)]
429
+  h <- breaks[-1] - breaks[-length(breaks)]
376 430
 
377
-    rect <- rectGrob(x = 0,
378
-        y = breaks[-length(breaks)],
379
-        width = unit(10, "bigpts"),
380
-        height = h,
381
-        hjust = 0,
382
-        vjust = 0,
383
-        gp = gpar(fill = color, col = "#FFFFFF00"))
431
+  rect <- rectGrob(
432
+    x = 0,
433
+    y = breaks[-length(breaks)],
434
+    width = unit(10, "bigpts"),
435
+    height = h,
436
+    hjust = 0,
437
+    vjust = 0,
438
+    gp = gpar(fill = color, col = "#FFFFFF00")
439
+  )
384 440
 
385
-    text <- textGrob(names(legend),
386
-        x = unit(14, "bigpts"),
387
-        y = legendPos,
388
-        hjust = 0,
389
-        gp = gpar(...))
441
+  text <- textGrob(names(legend),
442
+    x = unit(14, "bigpts"),
443
+    y = legendPos,
444
+    hjust = 0,
445
+    gp = gpar(...)
446
+  )
390 447
 
391
-    res <- grobTree(rect, text)
448
+  res <- grobTree(rect, text)
392 449
 
393
-    return(res)
450
+  return(res)
394 451
 }
395 452
 
396 453
 .convertAnnotations <- function(annotation, annotationColors) {
397
-    new <- annotation
398
-    for (i in seq(ncol(annotation))) {
399
-        a <- annotation[, i]
400
-        b <- annotationColors[[colnames(annotation)[i]]]
401
-        if (is.character(a) | is.factor(a)) {
402
-            a <- as.character(a)
403
-
404
-            if (length(setdiff(setdiff(a, NA), names(b))) > 0) {
405
-                stop(sprintf("Factor levels on variable %s do not match
454
+  new <- annotation
455
+  for (i in seq(ncol(annotation))) {
456
+    a <- annotation[, i]
457
+    b <- annotationColors[[colnames(annotation)[i]]]
458
+    if (is.character(a) | is.factor(a)) {
459
+      a <- as.character(a)
460
+
461
+      if (length(setdiff(setdiff(a, NA), names(b))) > 0) {
462
+        stop(sprintf(
463
+          "Factor levels on variable %s do not match
406 464
                         with annotationColors",
407
-                    colnames(annotation)[i]))
408
-            }
409
-            new[, i] <- b[a]
410
-        } else {
411
-            a <- cut(a, breaks = 100)
412
-            new[, i] <- colorRampPalette(b)(100)[a]
413
-        }
465
+          colnames(annotation)[i]
466
+        ))
467
+      }
468
+      new[, i] <- b[a]
469
+    } else {
470
+      a <- cut(a, breaks = 100)
471
+      new[, i] <- colorRampPalette(b)(100)[a]
414 472
     }
415
-    return(as.matrix(new))
473
+  }
474
+  return(as.matrix(new))
416 475
 }
417 476
 
418 477
 .drawAnnotations <- function(convertedAnnotations,
419
-    borderColor,
420
-    gaps,
421
-    fontSize,
422
-    horizontal) {
423
-
424
-    n <- ncol(convertedAnnotations)
425
-    m <- nrow(convertedAnnotations)
426
-
427
-    coordX <- .findCoordinates(m, gaps)
428
-
429
-    x <- coordX$coord - 0.5 * coordX$size
430
-
431
-    # y = cumsum(rep(fontSize, n)) - 4 + cumsum(rep(2, n))
432
-    y <- cumsum(rep(fontSize, n)) +
433
-        cumsum(rep(2, n)) -
434
-        fontSize / 2 + 1
435
-    y <- unit(y, "bigpts")
478
+                             borderColor,
479
+                             gaps,
480
+                             fontSize,
481
+                             horizontal) {
482
+  n <- ncol(convertedAnnotations)
483
+  m <- nrow(convertedAnnotations)
484
+
485
+  coordX <- .findCoordinates(m, gaps)
486
+
487
+  x <- coordX$coord - 0.5 * coordX$size
488
+
489
+  # y = cumsum(rep(fontSize, n)) - 4 + cumsum(rep(2, n))
490
+  y <- cumsum(rep(fontSize, n)) +
491
+    cumsum(rep(2, n)) -
492
+    fontSize / 2 + 1
493
+  y <- unit(y, "bigpts")
494
+
495
+  if (horizontal) {
496
+    coord <- expand.grid(x = x, y = y)
497
+    res <- rectGrob(
498
+      x = coord$x,
499
+      y = coord$y,
500
+      width = coordX$size,
501
+      height = unit(fontSize, "bigpts"),