]> git.donarmstrong.com Git - ape.git/blob - R/plot.phylo.R
bug fix in write.tree()
[ape.git] / R / plot.phylo.R
1 ## plot.phylo.R (2008-05-08)
2
3 ##   Plot Phylogenies
4
5 ## Copyright 2002-2008 Emmanuel Paradis
6
7 ## This file is part of the R-package `ape'.
8 ## See the file ../COPYING for licensing issues.
9
10 plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
11                        node.pos = NULL, show.tip.label = TRUE,
12                        show.node.label = FALSE, edge.color = "black",
13                        edge.width = 1, font = 3, cex = par("cex"),
14                        adj = NULL, srt = 0, no.margin = FALSE,
15                        root.edge = FALSE, label.offset = 0, underscore = FALSE,
16                        x.lim = NULL, y.lim = NULL, direction = "rightwards",
17                        lab4ut = "horizontal", tip.color = "black", ...)
18 {
19     Ntip <- length(x$tip.label)
20     if (Ntip == 1) stop("found only one tip in the tree!")
21     Nedge <- dim(x$edge)[1]
22     if (any(tabulate(x$edge[, 1]) == 1))
23       stop("there are single (non-splitting) nodes in your tree; you may need to use collapse.singles().")
24     Nnode <- x$Nnode
25     ROOT <- Ntip + 1
26     type <- match.arg(type, c("phylogram", "cladogram", "fan",
27                               "unrooted", "radial"))
28     direction <- match.arg(direction, c("rightwards", "leftwards",
29                                         "upwards", "downwards"))
30     if (is.null(x$edge.length)) use.edge.length <- FALSE
31     if (type == "unrooted" || !use.edge.length) root.edge <- FALSE
32     phyloORclado <- type %in% c("phylogram", "cladogram")
33     horizontal <- direction %in% c("rightwards", "leftwards")
34     if (phyloORclado) {
35         ## we first compute the y-coordinates of the tips.
36         ## Fix from Klaus Schliep (2007-06-16):
37         if (!is.null(attr(x, "order")))
38           if (attr(x, "order") == "pruningwise")
39             x <- reorder(x)
40         ## End of fix
41         yy <- numeric(Ntip + Nnode)
42         TIPS <- x$edge[x$edge[, 2] <= Ntip, 2]
43         yy[TIPS] <- 1:Ntip
44     }
45     edge.color <- rep(edge.color, length.out = Nedge)
46     edge.width <- rep(edge.width, length.out = Nedge)
47     ## fix from Li-San Wang (2007-01-23):
48     xe <- x$edge
49     x <- reorder(x, order = "pruningwise")
50     ereorder <- match(x$edge[, 2], xe[, 2])
51     edge.color <- edge.color[ereorder]
52     edge.width <- edge.width[ereorder]
53     ## End of fix
54     if (phyloORclado) {
55         if (is.null(node.pos)) {
56             node.pos <- 1
57             if (type == "cladogram" && !use.edge.length) node.pos <- 2
58         }
59         if (node.pos == 1)
60           yy <- .C("node_height", as.integer(Ntip), as.integer(Nnode),
61                    as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
62                    as.integer(Nedge), as.double(yy),
63                    DUP = FALSE, PACKAGE = "ape")[[6]]
64         else {
65           ## node_height_clado requires the number of descendants
66           ## for each node, so we compute `xx' at the same time
67           ans <- .C("node_height_clado", as.integer(Ntip),
68                     as.integer(Nnode), as.integer(x$edge[, 1]),
69                     as.integer(x$edge[, 2]), as.integer(Nedge),
70                     double(Ntip + Nnode), as.double(yy),
71                     DUP = FALSE, PACKAGE = "ape")
72           xx <- ans[[6]] - 1
73           yy <- ans[[7]]
74         }
75         if (!use.edge.length) {
76             if(node.pos != 2)
77               xx <- .C("node_depth", as.integer(Ntip), as.integer(Nnode),
78                        as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
79                        as.integer(Nedge), double(Ntip + Nnode),
80                        DUP = FALSE, PACKAGE = "ape")[[6]] - 1
81             xx <- max(xx) - xx
82         } else  {
83               xx <- .C("node_depth_edgelength", as.integer(Ntip),
84                        as.integer(Nnode), as.integer(x$edge[, 1]),
85                        as.integer(x$edge[, 2]), as.integer(Nedge),
86                        as.double(x$edge.length), double(Ntip + Nnode),
87                        DUP = FALSE, PACKAGE = "ape")[[7]]
88         }
89     }
90     if (type == "fan") {
91         ## if the tips are not in the same order in tip.label
92         ## and in edge[, 2], we must reorder the angles: we
93         ## use `xx' to store temporarily the angles
94         TIPS <- xe[which(xe[, 2] <= Ntip), 2]
95         xx <- seq(0, 2*pi*(1 - 1/Ntip), 2*pi/Ntip)
96         theta <- double(Ntip)
97         theta[TIPS] <- xx
98         theta <- c(theta, numeric(Nnode))
99         theta <- .C("node_height", as.integer(Ntip), as.integer(Nnode),
100                   as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
101                   as.integer(Nedge), theta, DUP = FALSE,
102                   PACKAGE = "ape")[[6]]
103         if (use.edge.length) {
104             r <- .C("node_depth_edgelength", as.integer(Ntip),
105                     as.integer(Nnode), as.integer(x$edge[, 1]),
106                     as.integer(x$edge[, 2]), as.integer(Nedge),
107                     as.double(x$edge.length), double(Ntip + Nnode),
108                     DUP = FALSE, PACKAGE = "ape")[[7]]
109         } else {
110             r <- .C("node_depth", as.integer(Ntip), as.integer(Nnode),
111                     as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
112                     as.integer(Nedge), double(Ntip + Nnode),
113                     DUP = FALSE, PACKAGE = "ape")[[6]]
114             r <- 1/r
115         }
116         xx <- r*cos(theta)
117         yy <- r*sin(theta)
118
119     }
120     if (type == "unrooted") {
121         XY <- if (use.edge.length)
122           unrooted.xy(Ntip, Nnode, x$edge, x$edge.length)
123         else
124           unrooted.xy(Ntip, Nnode, x$edge, rep(1, Nedge))
125         ## rescale so that we have only positive values
126         xx <- XY$M[, 1] - min(XY$M[, 1])
127         yy <- XY$M[, 2] - min(XY$M[, 2])
128     }
129     if (type == "radial") {
130         X <- .C("node_depth", as.integer(Ntip), as.integer(Nnode),
131                 as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
132                 as.integer(Nedge), double(Ntip + Nnode),
133                 DUP = FALSE, PACKAGE = "ape")[[6]]
134         X[X == 1] <- 0
135         ## radius:
136         X <- 1 - X/Ntip
137         ## angle (1st compute the angles for the tips):
138         yy <- c((1:Ntip)*2*pi/Ntip, rep(0, Nnode))
139         Y <- .C("node_height", as.integer(Ntip), as.integer(Nnode),
140                 as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
141                 as.integer(Nedge), as.double(yy),
142                 DUP = FALSE, PACKAGE = "ape")[[6]]
143         xx <- X * cos(Y)
144         yy <- X * sin(Y)
145     }
146     if (phyloORclado && direction != "rightwards") {
147         if (direction == "leftwards") {
148             xx <- -xx
149             xx <- xx - min(xx)
150         }
151         if (!horizontal) {
152             tmp <- yy
153             yy <- xx
154             xx <- tmp - min(tmp) + 1
155             if (direction == "downwards") {
156                 yy <- -yy
157                 yy <- yy - min(yy)
158             }
159         }
160     }
161     if (phyloORclado && root.edge) {
162         if (direction == "rightwards") xx <- xx + x$root.edge
163         if (direction == "upwards") yy <- yy + x$root.edge
164     }
165     if (no.margin) par(mai = rep(0, 4))
166     if (is.null(x.lim)) {
167         if (phyloORclado) {
168             if (horizontal) {
169                 x.lim <- c(0, NA)
170                 tmp <-
171                   if (show.tip.label) nchar(x$tip.label) * 0.018 * max(xx) * cex
172                   else 0
173                 x.lim[2] <-
174                   if (direction == "leftwards") max(xx[ROOT] + tmp)
175                   else max(xx[1:Ntip] + tmp)
176             } else x.lim <- c(1, Ntip)
177         }
178         if (type == "fan") {
179             if (show.tip.label) {
180                 offset <- max(nchar(x$tip.label) * 0.018 * max(yy) * cex)
181                 x.lim <- c(min(xx) - offset, max(xx) + offset)
182             } else x.lim <- c(min(xx), max(xx))
183         }
184         if (type == "unrooted") {
185             if (show.tip.label) {
186                 offset <- max(nchar(x$tip.label) * 0.018 * max(yy) * cex)
187                 x.lim <- c(0 - offset, max(xx) + offset)
188             } else x.lim <- c(0, max(xx))
189         }
190         if (type == "radial") {
191             if (show.tip.label) {
192                 offset <- max(nchar(x$tip.label) * 0.03 * cex)
193                 x.lim <- c(-1 - offset, 1 + offset)
194             } else x.lim <- c(-1, 1)
195         }
196     } else if (length(x.lim) == 1) {
197         x.lim <- c(0, x.lim)
198         if (phyloORclado && !horizontal) x.lim[1] <- 1
199         if (type %in% c("fan", "unrooted") && show.tip.label)
200           x.lim[1] <- -max(nchar(x$tip.label) * 0.018 * max(yy) * cex)
201         if (type == "radial")
202           x.lim[1] <-
203             if (show.tip.label) -1 - max(nchar(x$tip.label) * 0.03 * cex)
204             else -1
205     }
206     if (is.null(y.lim)) {
207         if (phyloORclado) {
208             if (horizontal) y.lim <- c(1, Ntip) else {
209                 y.lim <- c(0, NA)
210                 tmp <-
211                   if (show.tip.label) nchar(x$tip.label) * 0.018 * max(yy) * cex
212                   else 0
213                 y.lim[2] <-
214                   if (direction == "downwards") max(yy[ROOT] + tmp)
215                   else max(yy[1:Ntip] + tmp)
216             }
217         }
218         if (type == "fan") {
219             if (show.tip.label) {
220                 offset <- max(nchar(x$tip.label) * 0.018 * max(yy) * cex)
221                 y.lim <- c(min(yy) - offset, max(yy) + offset)
222             } else y.lim <- c(min(yy), max(yy))
223         }
224         if (type == "unrooted") {
225             if (show.tip.label) {
226                 offset <- max(nchar(x$tip.label) * 0.018 * max(yy) * cex)
227                 y.lim <- c(0 - offset, max(yy) + offset)
228             } else y.lim <- c(0, max(yy))
229         }
230         if (type == "radial") {
231             if (show.tip.label) {
232                 offset <- max(nchar(x$tip.label) * 0.03 * cex)
233                 y.lim <- c(-1 - offset, 1 + offset)
234             } else y.lim <- c(-1, 1)
235         }
236     } else if (length(y.lim) == 1) {
237         y.lim <- c(0, y.lim)
238         if (phyloORclado && horizontal) y.lim[1] <- 1
239         if (type %in% c("fan", "unrooted") && show.tip.label)
240           y.lim[1] <- -max(nchar(x$tip.label) * 0.018 * max(yy) * cex)
241         if (type == "radial")
242           y.lim[1] <- if (show.tip.label) -1 - max(nchar(x$tip.label) * 0.018 * max(yy) * cex) else -1
243     }
244     if (phyloORclado && root.edge) {
245         if (direction == "leftwards") x.lim[2] <- x.lim[2] + x$root.edge
246         if (direction == "downwards") y.lim[2] <- y.lim[2] + x$root.edge
247     }
248     ## fix by Klaus Schliep (2008-03-28):
249     asp <- if (type %in% c("fan", "radial")) 1 else NA
250     plot(0, type = "n", xlim = x.lim, ylim = y.lim, xlab = "",
251          ylab = "", xaxt = "n", yaxt = "n", bty = "n", asp = asp, ...)
252     if (is.null(adj))
253       adj <- if (phyloORclado && direction == "leftwards") 1 else 0
254     if (phyloORclado) {
255         MAXSTRING <- max(strwidth(x$tip.label, cex = cex))
256         if (direction == "rightwards") {
257             lox <- label.offset + MAXSTRING * 1.05 * adj
258             loy <- 0
259         }
260         if (direction == "leftwards") {
261             lox <- -label.offset - MAXSTRING * 1.05 * (1 - adj)
262             loy <- 0
263             xx <- xx + MAXSTRING
264         }
265         if (!horizontal) {
266             psr <- par("usr")
267             MAXSTRING <- MAXSTRING * 1.09 * (psr[4] - psr[3]) / (psr[2] - psr[1])
268             loy <- label.offset + MAXSTRING * 1.05 * adj
269             lox <- 0
270             srt <- 90 + srt
271             if (direction == "downwards") {
272                 loy <- -loy
273                 yy <- yy + MAXSTRING
274                 srt <- 180 + srt
275             }
276         }
277     }
278     if (type == "phylogram") {
279         phylogram.plot(x$edge, Ntip, Nnode, xx, yy,
280                        horizontal, edge.color, edge.width)
281     } else {
282       if (type == "fan")
283         circular.plot(x$edge, Ntip, Nnode, xx, yy, theta,
284                       r, edge.color, edge.width)
285       else
286         cladogram.plot(x$edge, xx, yy, edge.color, edge.width)
287     }
288     if (root.edge)
289       switch(direction,
290              "rightwards" = segments(0, yy[ROOT], x$root.edge, yy[ROOT]),
291              "leftwards" = segments(xx[ROOT], yy[ROOT], xx[ROOT] + x$root.edge, yy[ROOT]),
292              "upwards" = segments(xx[ROOT], 0, xx[ROOT], x$root.edge),
293              "downwards" = segments(xx[ROOT], yy[ROOT], xx[ROOT], yy[ROOT] + x$root.edge))
294     if (show.tip.label) {
295         if (!underscore) x$tip.label <- gsub("_", " ", x$tip.label)
296         if (phyloORclado) {
297             text(xx[1:Ntip] + lox, yy[1:Ntip] + loy, x$tip.label, adj = adj,
298                  font = font, srt = srt, cex = cex, col = tip.color)
299         }
300         if (type == "unrooted") {
301             if (lab4ut == "horizontal") {
302                 y.adj <- x.adj <- numeric(Ntip)
303                 sel <- abs(XY$axe) > 0.75 * pi
304                 x.adj[sel] <- -strwidth(x$tip.label)[sel] * 1.05
305                 sel <- abs(XY$axe) > pi/4 & abs(XY$axe) < 0.75 * pi
306                 x.adj[sel] <- -strwidth(x$tip.label)[sel] * (2 * abs(XY$axe)[sel] / pi - 0.5)
307                 sel <- XY$axe > pi / 4 & XY$axe < 0.75 * pi
308                 y.adj[sel] <- strheight(x$tip.label)[sel] / 2
309                 sel <- XY$axe < -pi / 4 & XY$axe > -0.75 * pi
310                 y.adj[sel] <- -strheight(x$tip.label)[sel] * 0.75
311                 text(xx[1:Ntip] + x.adj*cex, yy[1:Ntip] + y.adj*cex,
312                      x$tip.label, adj = c(adj, 0), font = font,
313                      srt = srt, cex = cex, col = tip.color)
314             } else { # if lab4ut == "axial"
315                 adj <- as.numeric(abs(XY$axe) > pi/2)
316                 srt <- 180*XY$axe/pi
317                 srt[as.logical(adj)] <- srt[as.logical(adj)] - 180
318                 ## <FIXME> temporary check of the values of `srt':
319                 ## set to 0 if "-0.000001 < srt < 0"
320                 sel <- srt > -1e-6 & srt < 0
321                 if (any(sel)) srt[sel] <- 0
322                 ## </FIXME>
323                 ## `srt' takes only a single value, so we cannot vectorize this:
324                 for (i in 1:Ntip)
325                   text(xx[i], yy[i], cex = cex, x$tip.label[i], adj = adj[i],
326                        font = font, srt = srt[i], col = tip.color[i])
327             }
328         }
329         if (type %in% c("fan", "radial")) {
330             xx.scaled <- xx[1:Ntip]
331             if (type == "fan") { # no need if type == "radial"
332                 maxx <- max(abs(xx.scaled))
333                 if (maxx > 1) xx.scaled <- xx.scaled/maxx
334             }
335             angle <- acos(xx.scaled)*180/pi
336             s1 <- angle > 90 & yy[1:Ntip] > 0
337             s2 <- angle < 90 & yy[1:Ntip] < 0
338             s3 <- angle > 90 & yy[1:Ntip] < 0
339             angle[s1] <- angle[s1] + 180
340             angle[s2] <- -angle[s2]
341             angle[s3] <- 180 - angle[s3]
342             adj <- numeric(Ntip)
343             adj[xx[1:Ntip] < 0] <- 1
344             ## `srt' takes only a single value, so we cannot vectorize this:
345             for (i in 1:Ntip)
346               text(xx[i], yy[i], x$tip.label[i], font = font, cex = cex,
347                    srt = angle[i], adj = adj[i], col = tip.color[i])
348         }
349     }
350     if (show.node.label)
351       text(xx[ROOT:length(xx)] + label.offset, yy[ROOT:length(yy)],
352            x$node.label, adj = adj, font = font, srt = srt, cex = cex)
353     L <- list(type = type, use.edge.length = use.edge.length,
354               node.pos = node.pos, show.tip.label = show.tip.label,
355               show.node.label = show.node.label, font = font,
356               cex = cex, adj = adj, srt = srt, no.margin = no.margin,
357               label.offset = label.offset, x.lim = x.lim, y.lim = y.lim,
358               direction = direction, tip.color = tip.color,
359               Ntip = Ntip, Nnode = Nnode)
360     assign("last_plot.phylo", c(L, list(edge = xe, xx = xx, yy = yy)),
361            envir = .PlotPhyloEnv)
362     invisible(L)
363 }
364
365 phylogram.plot <- function(edge, Ntip, Nnode, xx, yy,
366                            horizontal, edge.color, edge.width)
367 {
368     nodes <- (Ntip + 1):(Ntip + Nnode)
369     if (!horizontal) {
370         tmp <- yy
371         yy <- xx
372         xx <- tmp
373     }
374     ## un trait vertical à chaque noeud...
375     x0v <- xx[nodes]
376     y0v <- y1v <- numeric(Nnode)
377     for (i in nodes) {
378         j <- edge[which(edge[, 1] == i), 2]
379         y0v[i - Ntip] <- min(yy[j])
380         y1v[i - Ntip] <- max(yy[j])
381     }
382     ## ... et un trait horizontal partant de chaque tip et chaque noeud
383     ##  vers la racine
384     sq <- if (Nnode == 1) 1:Ntip else c(1:Ntip, nodes[-1])
385     y0h <- yy[sq]
386     x1h <- xx[sq]
387     ## match() is very useful here becoz each element in edge[, 2] is
388     ## unique (not sure this is so useful in edge[, 1]; needs to be checked)
389     ## `pos' gives for each element in `sq' its index in edge[, 2]
390     pos <- match(sq, edge[, 2])
391     x0h <- xx[edge[pos, 1]]
392
393     e.w <- unique(edge.width)
394     if (length(e.w) == 1) width.v <- rep(e.w, Nnode)
395     else {
396         width.v <- rep(1, Nnode)
397         for (i in 1:Nnode) {
398             br <- edge[which(edge[, 1] == i + Ntip), 2]
399             width <- unique(edge.width[br])
400             if (length(width) == 1) width.v[i] <- width
401         }
402     }
403     e.c <- unique(edge.color)
404     if (length(e.c) == 1) color.v <- rep(e.c, Nnode)
405     else {
406         color.v <- rep("black", Nnode)
407         for (i in 1:Nnode) {
408             br <- which(edge[, 1] == i + Ntip)
409             #br <- edge[which(edge[, 1] == i + Ntip), 2]
410             color <- unique(edge.color[br])
411             if (length(color) == 1) color.v[i] <- color
412         }
413     }
414
415     ## we need to reorder `edge.color' and `edge.width':
416     edge.width <- edge.width[pos]
417     edge.color <- edge.color[pos]
418     if (horizontal) {
419         segments(x0v, y0v, x0v, y1v, col = color.v, lwd = width.v) # draws vertical lines
420         segments(x0h, y0h, x1h, y0h, col = edge.color, lwd = edge.width) # draws horizontal lines
421     } else {
422         segments(y0v, x0v, y1v, x0v, col = color.v, lwd = width.v) # draws horizontal lines
423         segments(y0h, x0h, y0h, x1h, col = edge.color, lwd = edge.width) # draws vertical lines
424     }
425 }
426
427 cladogram.plot <- function(edge, xx, yy, edge.color, edge.width)
428   segments(xx[edge[, 1]], yy[edge[, 1]], xx[edge[, 2]], yy[edge[, 2]],
429            col = edge.color, lwd = edge.width)
430
431 circular.plot <- function(edge, Ntip, Nnode, xx, yy, theta,
432                           r, edge.color, edge.width)
433 {
434     r0 <- r[edge[, 1]]
435     r1 <- r[edge[, 2]]
436     theta0 <- theta[edge[, 2]]
437
438     x0 <- r0*cos(theta0)
439     y0 <- r0*sin(theta0)
440     x1 <- r1*cos(theta0)
441     y1 <- r1*sin(theta0)
442
443     segments(x0, y0, x1, y1, col = edge.color, lwd = edge.width)
444
445     tmp <- which(diff(edge[, 1]) != 0)
446     start <- c(1, tmp + 1)
447     end <- c(tmp, dim(edge)[1])
448
449     for (k in 1:Nnode) {
450         i <- start[k]
451         j <- end[k]
452         X <- rep(r[edge[i, 1]], 100)
453         Y <- seq(theta[edge[i, 2]], theta[edge[j, 2]], length.out = 100)
454         co <- if (edge.color[i] == edge.color[j]) edge.color[i] else "black"
455         lw <- if (edge.width[i] == edge.width[j]) edge.width[i] else 1
456         lines(X*cos(Y), X*sin(Y), col = co, lwd = lw)
457     }
458 }
459
460 unrooted.xy <- function(Ntip, Nnode, edge, edge.length)
461 {
462     foo <- function(node, ANGLE, AXIS) {
463         ind <- which(edge[, 1] == node)
464         sons <- edge[ind, 2]
465         start <- AXIS - ANGLE/2
466         for (i in 1:length(sons)) {
467             h <- edge.length[ind[i]]
468             angle[sons[i]] <<- alpha <- ANGLE*nb.sp[sons[i]]/nb.sp[node]
469             axis[sons[i]] <<- beta <- start + alpha/2
470             start <- start + alpha
471             xx[sons[i]] <<- h*cos(beta) + xx[node]
472             yy[sons[i]] <<- h*sin(beta) + yy[node]
473         }
474         for (i in sons)
475           if (i > Ntip) foo(i, angle[i], axis[i])
476     }
477     root <- Ntip + 1
478     Nedge <- dim(edge)[1]
479     yy <- xx <- numeric(Ntip + Nnode)
480     nb.sp <- .C("node_depth", as.integer(Ntip), as.integer(Nnode),
481                 as.integer(edge[, 1]), as.integer(edge[, 2]),
482                 as.integer(Nedge), double(Ntip + Nnode),
483                 DUP = FALSE, PACKAGE = "ape")[[6]]
484     ## `angle': the angle allocated to each node wrt their nb of tips
485     ## `axis': the axis of each branch
486     axis <- angle <- numeric(Ntip + Nnode)
487     ## start with the root...
488     ## xx[root] <- yy[root] <- 0 # already set!
489     foo(root, 2*pi, 0)
490
491     M <- cbind(xx, yy)
492     axe <- axis[1:Ntip] # the axis of the terminal branches (for export)
493     axeGTpi <- axe > pi
494     ## insures that returned angles are in [-PI, +PI]:
495     axe[axeGTpi] <- axe[axeGTpi] - 2*pi
496     list(M = M, axe = axe)
497 }
498
499 node.depth <- function(phy)
500 {
501     n <- length(phy$tip.label)
502     m <- phy$Nnode
503     N <- dim(phy$edge)[1]
504     phy <- reorder(phy, order = "pruningwise")
505     .C("node_depth", as.integer(n), as.integer(m),
506        as.integer(phy$edge[, 1]), as.integer(phy$edge[, 2]),
507        as.integer(N), double(n + m), DUP = FALSE, PACKAGE = "ape")[[6]]
508 }
509
510 plot.multiPhylo <- function(x, layout = 1, ...)
511 {
512     if (layout > 1)
513       layout(matrix(1:layout, ceiling(sqrt(layout)), byrow = TRUE))
514     else layout(matrix(1))
515     if (!par("ask")) {
516         par(ask = TRUE)
517         on.exit(par(ask = FALSE))
518     }
519     for (i in 1:length(x)) plot(x[[i]], ...)
520 }