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