X-Git-Url: https://git.donarmstrong.com/?a=blobdiff_plain;f=R%2Fdist.topo.R;h=525178f2528ed1ba66321e178d8c79d2cf0c91ed;hb=a02ce8c6e9fd80d3d7a749cc24699366fb8e54b6;hp=d94866adfe1c65f9c46946567573196b6a4e51a9;hpb=bfaeca35ec130110327a3bb7a1f0fe3b66076a95;p=ape.git diff --git a/R/dist.topo.R b/R/dist.topo.R index d94866a..525178f 100644 --- a/R/dist.topo.R +++ b/R/dist.topo.R @@ -1,4 +1,4 @@ -## dist.topo.R (2011-02-21) +## dist.topo.R (2011-07-13) ## Topological Distances, Tree Bipartitions, ## Consensus Trees, and Bootstrapping Phylogenies @@ -71,23 +71,26 @@ dist.topo <- function(x, y, method = "PH85") if (any(table(ref) != 1)) stop("some tip labels are duplicated in tree no. 1") n <- length(ref) - for (i in 2:length(x)) { - label <- x[[i]]$tip.label - if (!identical(label, ref)) { - if (length(label) != length(ref)) - stop(paste("tree no.", i, "has a different number of tips")) - ilab <- match(label, ref) - ## can use tabulate here because 'ilab' contains integers - if (any(is.na(ilab))) - stop(paste("tree no.", i, "has different tip labels")) + Ntree <- length(x) + if (Ntree > 1) { + for (i in 2:Ntree) { + label <- x[[i]]$tip.label + if (!identical(label, ref)) { + if (length(label) != length(ref)) + stop(paste("tree no.", i, "has a different number of tips")) + ilab <- match(label, ref) + ## can use tabulate here because 'ilab' contains integers + if (any(is.na(ilab))) + stop(paste("tree no.", i, "has different tip labels")) ### the test below does not seem useful anymore ### if (any(tabulate(ilab) > 1)) ### stop(paste("some tip labels are duplicated in tree no.", i)) ### - ie <- match(1:n, x[[i]]$edge[, 2]) - x[[i]]$edge[ie, 2] <- ilab + ie <- match(1:n, x[[i]]$edge[, 2]) + x[[i]]$edge[ie, 2] <- ilab + } + x[[i]]$tip.label <- NULL } - x[[i]]$tip.label <- NULL } x[[1]]$tip.label <- NULL attr(x, "TipLabel") <- ref @@ -181,7 +184,8 @@ prop.clades <- function(phy, ..., part = NULL) n } -boot.phylo <- function(phy, x, FUN, B = 100, block = 1, trees = FALSE) +boot.phylo <- function(phy, x, FUN, B = 100, block = 1, + trees = FALSE, quiet = FALSE) { if (is.list(x) && !is.data.frame(x)) { if (inherits(x, "DNAbin")) x <- as.matrix(x) @@ -195,6 +199,7 @@ boot.phylo <- function(phy, x, FUN, B = 100, block = 1, trees = FALSE) } } boot.tree <- vector("list", B) + if (!quiet) progbar <- utils::txtProgressBar(style = 3) # suggestion by Alastair Potts for (i in 1:B) { if (block > 1) { y <- seq(block, ncol(x), block) @@ -205,11 +210,14 @@ boot.phylo <- function(phy, x, FUN, B = 100, block = 1, trees = FALSE) boot.samp[y - j] <- boot.i - j } else boot.samp <- sample(ncol(x), replace = TRUE) boot.tree[[i]] <- FUN(x[, boot.samp]) + if (!quiet) utils::setTxtProgressBar(progbar, i/B) } + if (!quiet) close(progbar) for (i in 1:B) storage.mode(boot.tree[[i]]$Nnode) <- "integer" storage.mode(phy$Nnode) <- "integer" - ans <- attr(.Call("prop_part", c(list(phy), boot.tree), - B + 1, FALSE, PACKAGE = "ape"), "number") - 1 + ans <- prop.clades(phy, boot.tree) + ##ans <- attr(.Call("prop_part", c(list(phy), boot.tree), + ## B + 1, FALSE, PACKAGE = "ape"), "number") - 1 if (trees) { class(boot.tree) <- "multiPhylo" ans <- list(BP = ans, trees = boot.tree) @@ -260,6 +268,7 @@ consensus <- function(..., p = 1, check.labels = TRUE) ## Get all observed partitions and their frequencies: pp <- prop.part(obj, check.labels = FALSE) ## Drop the partitions whose frequency is less than 'p': + if (p == 0.5) p <- 0.5000001 # avoid incompatible splits pp <- pp[attr(pp, "number") >= p * ntree] ## Get the order of the remaining partitions by decreasing size: ind <- sort(unlist(lapply(pp, length)), decreasing = TRUE,