]> git.donarmstrong.com Git - ape.git/blob - R/dist.topo.R
current 2.1 release
[ape.git] / R / dist.topo.R
1 ## dist.topo.R (2007-07-04)
2
3 ##      Topological Distances, Tree Bipartitions,
4 ##   Consensus Trees, and Bootstrapping Phylogenies
5
6 ## Copyright 2005-2007 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 prop.part <- function(..., check.labels = FALSE)
58 {
59     obj <- list(...)
60     if (length(obj) == 1 && class(obj[[1]]) != "phylo")
61       obj <- unlist(obj, recursive = FALSE)
62     ntree <- length(obj)
63     if (!check.labels) {
64         for (i in 1:ntree) storage.mode(obj[[i]]$Nnode) <- "integer"
65         clades <- .Call("prop_part", obj, ntree, TRUE, PACKAGE = "ape")
66         attr(clades, "number") <- attr(clades, "number")[1:length(clades)]
67         attr(clades, "labels") <- obj[[1]]$tip.label
68     } else {
69         bp <- .Call("bipartition", obj[[1]]$edge, length(obj[[1]]$tip.label),
70                     obj[[1]]$Nnode, PACKAGE = "ape")
71         clades <- lapply(bp, function(xx) sort(obj[[1]]$tip.label[xx]))
72         no <- rep(1, length(clades))
73
74         if (ntree > 1) {
75             for (k in 2:ntree) {
76                 bp <- .Call("bipartition", obj[[k]]$edge,
77                             length(obj[[k]]$tip.label), obj[[k]]$Nnode,
78                             PACKAGE = "ape")
79                 bp <- lapply(bp, function(xx) sort(obj[[k]]$tip.label[xx]))
80                 for (i in 1:length(bp)) {
81                     done <- FALSE
82                     for (j in 1:length(clades)) {
83                         if (identical(all.equal(bp[[i]], clades[[j]]), TRUE)) {
84                             no[j] <- no[j] + 1
85                             done <- TRUE
86                             break
87                         }
88                     }
89                     if (!done) {
90                         clades <- c(clades, bp[i])
91                         no <- c(no, 1)
92                     }
93                 }
94             }
95         }
96         attr(clades, "number") <- no
97     }
98     class(clades) <- "prop.part"
99     clades
100 }
101
102 print.prop.part <- function(x, ...)
103 {
104     if (is.null(attr(x, "labels"))) {
105         for (i in 1:length(x)) {
106             cat("==>", attr(x, "number")[i], "time(s):")
107             print(x[[i]], quote = FALSE)
108         }
109     } else {
110         for (i in 1:length(attr(x, "labels")))
111           cat(i, ": ", attr(x, "labels")[i], "\n", sep = "")
112         cat("\n")
113         for (i in 1:length(x)) {
114             cat("==>", attr(x, "number")[i], "time(s):")
115             print(x[[i]], quote = FALSE)
116         }
117     }
118 }
119
120 summary.prop.part <- function(object, ...) attr(object, "number")
121
122 plot.prop.part <- function(x, barcol = "blue", leftmar = 4, ...)
123 {
124     if (is.null(attr(x, "labels")))
125       stop("cannot plot this partition object; see ?prop.part for details.")
126     L <- length(x)
127     n <- length(attr(x, "labels"))
128     layout(matrix(1:2, 2, 1), heights = c(1, 3))
129     par(mar = c(0.1, leftmar, 0.1, 0.1))
130     plot(1:L, attr(x, "number"), type = "h", col = barcol, xlim = c(1, L),
131          xlab = "", ylab = "Number", xaxt = "n", bty = "n")
132     plot(0, type = "n", xlim = c(1, L), ylim = c(1, n),
133          xlab = "", ylab = "", xaxt = "n", yaxt = "n")
134     for (i in 1:L) points(rep(i, length(x[[i]])), x[[i]], ...)
135     mtext(attr(x, "labels"), side = 2, at = 1:n, las = 1)
136 }
137
138 prop.clades <- function(phy, ..., part = NULL)
139 {
140     if (is.null(part)) {
141         obj <- list(...)
142         if (length(obj) == 1 && class(obj[[1]]) != "phylo")
143           obj <- unlist(obj, recursive = FALSE)
144         part <- prop.part(obj, check.labels = TRUE)
145     }
146     bp <- .Call("bipartition", phy$edge, length(phy$tip.label),
147                 phy$Nnode, PACKAGE = "ape")
148     if (!is.null(attr(part, "labels")))
149       for (i in 1:length(part))
150         part[[i]] <- sort(attr(part, "labels")[part[[i]]])
151     bp <- lapply(bp, function(xx) sort(phy$tip.label[xx]))
152     n <- numeric(phy$Nnode)
153     for (i in 1:phy$Nnode) {
154         for (j in 1:length(part)) {
155             if (identical(all.equal(bp[[i]], part[[j]]), TRUE)) {
156                 n[i] <- attr(part, "number")[j]
157                 done <-  TRUE
158                 break
159             }
160         }
161     }
162     n
163 }
164
165 boot.phylo <- function(phy, x, FUN, B = 100, block = 1)
166 {
167     if (is.list(x)) {
168         nm <- names(x)
169         n <- length(x)
170         x <- unlist(x)
171         nL <- length(x)
172         x <- matrix(x, n, nL/n, byrow = TRUE)
173         rownames(x) <- nm
174     }
175     boot.tree <- vector("list", B)
176     for (i in 1:B) {
177         if (block > 1) {
178             y <- seq(block, ncol(x), block)
179             boot.i <- sample(y, replace = TRUE)
180             boot.samp <- numeric(ncol(x))
181             boot.samp[y] <- boot.i
182             for (j in 1:(block - 1))
183               boot.samp[y - j] <- boot.i - j
184         } else boot.samp <- sample(ncol(x), replace = TRUE)
185         boot.tree[[i]] <- FUN(x[, boot.samp])
186     }
187     for (i in 1:B) storage.mode(boot.tree[[i]]$Nnode) <- "integer"
188     storage.mode(phy$Nnode) <- "integer"
189     attr(.Call("prop_part", c(list(phy), boot.tree), B + 1, FALSE,
190                PACKAGE = "ape"), "number") - 1
191 }
192
193 consensus <- function(..., p = 1)
194 {
195     obj <- list(...)
196     if (length(obj) == 1 && class(obj[[1]]) != "phylo")
197       obj <- unlist(obj, recursive = FALSE)
198     ntree <- length(obj)
199     ## Get all observed partitions and their frequencies:
200     pp <- prop.part(obj, check.labels = TRUE)
201     ## Drop the partitions whose frequency is less than 'p':
202     pp <- pp[attr(pp, "number") >= p * ntree]
203     ## Get the order of the remaining partitions by decreasing size:
204     ind <- rev(sort(unlist(lapply(pp, length)),
205                     index.return = TRUE)$ix)
206     pp <- lapply(pp, function(xx) paste("IMPROBABLE_PREFIX", xx,
207                                         "IMPROBABLE_SUFFIX", sep = "_"))
208     STRING <- paste(pp[[1]], collapse = ",")
209     STRING <- paste("(", STRING, ");", sep = "")
210     for (i in ind[-1]) {
211         ## 1. Delete all tips in the focus partition:
212         STRING <- unlist(strsplit(STRING, paste(pp[[i]], collapse = "|")))
213         ## 2. Put the partition in any of the created gaps:
214         STRING <- c(STRING[1],
215                     paste("(", paste(pp[[i]], collapse = ","), ")", sep = ""),
216                     STRING[-1])
217         ## 3. Stick back the Newick string:
218         STRING <- paste(STRING, collapse = "")
219     }
220     ## Remove the extra commas:
221     STRING <- gsub(",{2,}", ",", STRING)
222     STRING <- gsub("\\(,", "\\(", STRING)
223     STRING <- gsub(",\\)", "\\)", STRING)
224     STRING <- gsub("IMPROBABLE_PREFIX_", "", STRING)
225     STRING <- gsub("_IMPROBABLE_SUFFIX", "", STRING)
226     read.tree(text = STRING)
227 }