]> git.donarmstrong.com Git - ape.git/blob - R/dist.topo.R
final wrap of ape 2.2
[ape.git] / R / dist.topo.R
1 ## dist.topo.R (2008-05-07)
2
3 ##      Topological Distances, Tree Bipartitions,
4 ##   Consensus Trees, and Bootstrapping Phylogenies
5
6 ## Copyright 2005-2008 Emmanuel Paradis
7
8 ## This file is part of the R-package `ape'.
9 ## See the file ../COPYING for licensing issues.
10
11 dist.topo <- function(x, y, method = "PH85")
12 {
13     if (method == "BHV01" && (is.null(x$edge.length) || is.null(y$edge.length)))
14       stop("trees must have branch lengths for Billera et al.'s distance.")
15     n <- length(x$tip.label)
16     bp1 <- .Call("bipartition", x$edge, n, x$Nnode, PACKAGE = "ape")
17     bp1 <- lapply(bp1, function(xx) sort(x$tip.label[xx]))
18     bp2 <- .Call("bipartition", y$edge, n, y$Nnode, PACKAGE = "ape")
19     bp2 <- lapply(bp2, function(xx) sort(y$tip.label[xx]))
20     q1 <- length(bp1)
21     q2 <- length(bp2)
22     if (method == "PH85") {
23         p <- 0
24         for (i in 1:q1) {
25             for (j in 1:q2) {
26                 if (identical(all.equal(bp1[[i]], bp2[[j]]), TRUE)) {
27                     p <- p + 1
28                     break
29                 }
30             }
31         }
32         dT <- if (q1 == q2) 2*(q1 - p) else 2*(min(q1, q2) - p) + abs(q1 - q2)
33     }
34     if (method == "BHV01") {
35         dT <- 0
36         found1 <- FALSE
37         found2 <- logical(q2)
38         found2[1] <- TRUE
39         for (i in 2:q1) {
40             for (j in 2:q2) {
41                 if (identical(bp1[[i]], bp2[[j]])) {
42                     dT <- dT + abs(x$edge.length[which(x$edge[, 2] == n + i)] -
43                                    y$edge.length[which(y$edge[, 2] == n + j)])
44                     found1 <- found2[j] <- TRUE
45                     break
46                 }
47             }
48             if (found1) found1 <- FALSE
49             else dT <- dT + x$edge.length[which(x$edge[, 2] == n + i)]
50         }
51         if (!all(found2))
52           dT <- dT + sum(y$edge.length[y$edge[, 2] %in% (n + which(!found2))])
53     }
54     dT
55 }
56
57 .compressTipLabel <- function(x)
58 {
59     ## 'x' is a list of objects of class "phylo" possibly with no class
60     if (!is.null(attr(x, "TipLabel"))) return(x)
61     ref <- x[[1]]$tip.label
62     if (any(table(ref) != 1))
63         stop("some tip labels are duplicated in tree no. 1")
64     n <- length(ref)
65     for (i in 2:length(x)) {
66         if (identical(x[[i]]$tip.label, ref)) next
67         ilab <- match(x[[i]]$tip.label, ref)
68         ## can use tabulate here because 'ilab' contains integers
69         if (any(tabulate(ilab) > 1))
70             stop(paste("some tip labels are duplicated in tree no.", i))
71         if (any(is.na(ilab)))
72             stop(paste("tree no.", i, "has different tip labels"))
73         ie <- match(1:n, x[[i]]$edge[, 2])
74         x[[i]]$edge[ie, 2] <- ilab
75     }
76     for (i in 1:length(x)) x[[i]]$tip.label <- NULL
77     attr(x, "TipLabel") <- ref
78     x
79 }
80
81 prop.part <- function(..., check.labels = FALSE)
82 {
83     obj <- list(...)
84     if (length(obj) == 1 && class(obj[[1]]) != "phylo")
85         obj <- obj[[1]]
86     ## <FIXME>
87     ## class(obj) <- NULL # needed?
88     ## </FIXME>
89     ntree <- length(obj)
90     if (check.labels) obj <- .compressTipLabel(obj)
91     for (i in 1:ntree) storage.mode(obj[[i]]$Nnode) <- "integer"
92     ## <FIXME>
93     ## The 1st must have tip labels
94     ## Maybe simply pass the number of tips to the C code??
95     if (!is.null(attr(obj, "TipLabel")))
96         for (i in 1:ntree) obj[[i]]$tip.label <- attr(obj, "TipLabel")
97     ## </FIXME>
98     clades <- .Call("prop_part", obj, ntree, TRUE, PACKAGE = "ape")
99     attr(clades, "number") <- attr(clades, "number")[1:length(clades)]
100     attr(clades, "labels") <- obj[[1]]$tip.label
101     class(clades) <- "prop.part"
102     clades
103 }
104
105 print.prop.part <- function(x, ...)
106 {
107     if (is.null(attr(x, "labels"))) {
108         for (i in 1:length(x)) {
109             cat("==>", attr(x, "number")[i], "time(s):")
110             print(x[[i]], quote = FALSE)
111         }
112     } else {
113         for (i in 1:length(attr(x, "labels")))
114           cat(i, ": ", attr(x, "labels")[i], "\n", sep = "")
115         cat("\n")
116         for (i in 1:length(x)) {
117             cat("==>", attr(x, "number")[i], "time(s):")
118             print(x[[i]], quote = FALSE)
119         }
120     }
121 }
122
123 summary.prop.part <- function(object, ...) attr(object, "number")
124
125 plot.prop.part <- function(x, barcol = "blue", leftmar = 4, ...)
126 {
127     if (is.null(attr(x, "labels")))
128       stop("cannot plot this partition object; see ?prop.part for details.")
129     L <- length(x)
130     n <- length(attr(x, "labels"))
131     layout(matrix(1:2, 2, 1), heights = c(1, 3))
132     par(mar = c(0.1, leftmar, 0.1, 0.1))
133     plot(1:L, attr(x, "number"), type = "h", col = barcol, xlim = c(1, L),
134          xlab = "", ylab = "Frequency", xaxt = "n", bty = "n")
135     plot(0, type = "n", xlim = c(1, L), ylim = c(1, n),
136          xlab = "", ylab = "", xaxt = "n", yaxt = "n")
137     for (i in 1:L) points(rep(i, length(x[[i]])), x[[i]], ...)
138     mtext(attr(x, "labels"), side = 2, at = 1:n, las = 1)
139 }
140
141 prop.clades <- function(phy, ..., part = NULL)
142 {
143     if (is.null(part)) {
144         obj <- list(...)
145         if (length(obj) == 1 && class(obj[[1]]) != "phylo")
146           obj <- unlist(obj, recursive = FALSE)
147         part <- prop.part(obj, check.labels = TRUE)
148     }
149     bp <- .Call("bipartition", phy$edge, length(phy$tip.label),
150                 phy$Nnode, PACKAGE = "ape")
151     if (!is.null(attr(part, "labels")))
152       for (i in 1:length(part))
153         part[[i]] <- sort(attr(part, "labels")[part[[i]]])
154     bp <- lapply(bp, function(xx) sort(phy$tip.label[xx]))
155     n <- numeric(phy$Nnode)
156     for (i in 1:phy$Nnode) {
157         for (j in 1:length(part)) {
158             if (identical(all.equal(bp[[i]], part[[j]]), TRUE)) {
159                 n[i] <- attr(part, "number")[j]
160                 done <-  TRUE
161                 break
162             }
163         }
164     }
165     n
166 }
167
168 boot.phylo <- function(phy, x, FUN, B = 100, block = 1, trees = FALSE)
169 {
170     if (is.list(x)) {
171         if (class(x) == "DNAbin") x <- as.matrix(x)
172         else {
173             nm <- names(x)
174             n <- length(x)
175             x <- unlist(x)
176             nL <- length(x)
177             x <- matrix(x, n, nL/n, byrow = TRUE)
178             rownames(x) <- nm
179         }
180     }
181     boot.tree <- vector("list", B)
182     for (i in 1:B) {
183         if (block > 1) {
184             y <- seq(block, ncol(x), block)
185             boot.i <- sample(y, replace = TRUE)
186             boot.samp <- numeric(ncol(x))
187             boot.samp[y] <- boot.i
188             for (j in 1:(block - 1))
189               boot.samp[y - j] <- boot.i - j
190         } else boot.samp <- sample(ncol(x), replace = TRUE)
191         boot.tree[[i]] <- FUN(x[, boot.samp])
192     }
193     for (i in 1:B) storage.mode(boot.tree[[i]]$Nnode) <- "integer"
194     storage.mode(phy$Nnode) <- "integer"
195     ans <- attr(.Call("prop_part", c(list(phy), boot.tree),
196                       B + 1, FALSE, PACKAGE = "ape"), "number") - 1
197     if (trees) ans <- list(BP = ans, trees = boot.tree)
198     ans
199 }
200
201 consensus <- function(..., p = 1, check.labels = FALSE)
202 {
203     foo <- function(ic, node) {
204         ## ic: index of 'pp'
205         ## node: node number in the final tree
206         pool <- pp[[ic]]
207         if (ic < m) {
208             for (j in (ic + 1):m) {
209                 wh <- match(pp[[j]], pool)
210                 if (!any(is.na(wh))) {
211                     edge[pos, 1] <<- node
212                     pool <- pool[-wh]
213                     edge[pos, 2] <<- nextnode <<- nextnode + 1L
214                     pos <<- pos + 1L
215                     foo(j, nextnode)
216                 }
217             }
218         }
219         size <- length(pool)
220         if (size) {
221             ind <- pos:(pos + size - 1)
222             edge[ind, 1] <<- node
223             edge[ind, 2] <<- pool
224             pos <<- pos + size
225         }
226     }
227     obj <- list(...)
228     if (length(obj) == 1) {
229         ## better than unlist(obj, recursive = FALSE)
230         ## because "[[" keeps the class of 'obj':
231         obj <- obj[[1]]
232         if (class(obj) == "phylo") return(obj)
233     }
234     if (!is.null(attr(obj, "TipLabel")))
235         labels <- attr(obj, "TipLabel")
236     else {
237         labels <- obj[[1]]$tip.label
238         if (check.labels) obj <- .compressTipLabel(obj)
239     }
240     ntree <- length(obj)
241     ## Get all observed partitions and their frequencies:
242     pp <- prop.part(obj, check.labels = FALSE)
243     ## Drop the partitions whose frequency is less than 'p':
244     pp <- pp[attr(pp, "number") >= p * ntree]
245     ## Get the order of the remaining partitions by decreasing size:
246     ind <- sort(unlist(lapply(pp, length)), decreasing = TRUE,
247                 index.return = TRUE)$ix
248     pp <- pp[ind]
249     n <- length(labels)
250     m <- length(pp)
251     edge <- matrix(0L, n + m - 1, 2)
252     if (m == 1) {
253         edge[, 1] <- n + 1L
254         edge[, 2] <- 1:n
255     } else {
256         nextnode <- n + 1L
257         pos <- 1L
258         foo(1, nextnode)
259     }
260     structure(list(edge = edge, tip.label = labels,
261               Nnode = m), class = "phylo")
262 }