X-Git-Url: https://git.donarmstrong.com/?a=blobdiff_plain;f=R%2Fdrop.tip.R;h=e9bd5c037364f4f8e20604ac3aff8ae6755a7b16;hb=da67dccb93d35408baa48b141fcda921772c8b9c;hp=e59b59b957a06ebf2a350b5d68d10741e3e3fbc4;hpb=6fe5709ee413e5a1a379918a70c64cee05e9ae54;p=ape.git diff --git a/R/drop.tip.R b/R/drop.tip.R index e59b59b..e9bd5c0 100644 --- a/R/drop.tip.R +++ b/R/drop.tip.R @@ -1,8 +1,8 @@ -## drop.tip.R (2010-02-11) +## drop.tip.R (2012-10-06) ## Remove Tips in a Phylogenetic Tree -## Copyright 2003-2010 Emmanuel Paradis +## Copyright 2003-2012 Emmanuel Paradis ## This file is part of the R-package `ape'. ## See the file ../COPYING for licensing issues. @@ -54,7 +54,11 @@ extract.clade <- function(phy, node, root.edge = 0, interactive = FALSE) if (wbl) phy$edge.length <- phy$edge.length[keep] TIPS <- phy$edge[, 2] <= Ntip tip <- phy$edge[TIPS, 2] - phy$tip.label <- phy$tip.label[tip] + ## Fix by Ludovic Mallet and Mahendra Mariadassou (2011-11-21): + name <- vector("character", length(tip)) + name[order(tip)] <- phy$tip.label[tip] + phy$tip.label <- name + ## End of fix ## keep the ordering so no need to reorder tip.label: phy$edge[TIPS, 2] <- order(tip) if (!is.null(phy$node.label)) @@ -79,6 +83,7 @@ drop.tip <- { if (!inherits(phy, "phylo")) stop('object "phy" is not of class "phylo"') + if (!length(tip)) return(phy) Ntip <- length(phy$tip.label) ## find the tips to drop: @@ -96,6 +101,8 @@ drop.tip <- if (is.character(tip)) tip <- which(phy$tip.label %in% tip) } + if (any(tip > Ntip)) + warning("some tip numbers were higher than the number of tips") if (!rooted && subtree) { phy <- root(phy, (1:Ntip)[-tip][1]) @@ -119,15 +126,6 @@ drop.tip <- edge2 <- phy$edge[, 2] # keep <- !logical(Nedge) - ## find the tips to drop: - if (is.character(tip)) - tip <- which(phy$tip.label %in% tip) - - if (!rooted && subtree) { - phy <- root(phy, (1:Ntip)[-tip][1]) - root.edge <- 0 - } - ## delete the terminal edges given by `tip': keep[match(tip, edge2)] <- FALSE @@ -179,21 +177,27 @@ drop.tip <- ## get the old No. of the nodes and tips that become tips: oldNo.ofNewTips <- phy$edge[TERMS, 2] + ## in case some tips are dropped but kept because of 'subtree = TRUE': + if (subtree) { + i <- which(tip %in% oldNo.ofNewTips) + if (length(i)) { + phy$tip.label[tip[i]] <- "[1_tip]" + tip <- tip[-i] + } + } + n <- length(oldNo.ofNewTips) # the new number of tips in the tree - ## the tips may not be sorted in increasing order of their - ## in the 2nd col of edge, so no need to reorder $tip.label + ## the tips may not be sorted in increasing order in the + ## 2nd col of edge, so no need to reorder $tip.label phy$edge[TERMS, 2] <- rank(phy$edge[TERMS, 2]) + phy$tip.label <- phy$tip.label[-tip] ## make new tip labels if necessary: if (subtree || !trim.internal) { - ## get the logical indices of the tips that are kept within 'oldNo.ofNewTips': - tips.kept <- oldNo.ofNewTips <= Ntip & !(oldNo.ofNewTips %in% tip) - new.tip.label <- character(n) - new.tip.label[tips.kept] <- phy$tip.label[-tip] ## get the numbers of the nodes that become tips: - node2tip <- oldNo.ofNewTips[!tips.kept] - new.tip.label[!tips.kept] <- if (subtree) { + node2tip <- oldNo.ofNewTips[oldNo.ofNewTips > Ntip] + new.tip.label <- if (subtree) { paste("[", N[node2tip], "_tips]", sep = "") } else { if (is.null(phy$node.label)) rep("NA", length(node2tip)) @@ -201,17 +205,13 @@ drop.tip <- } if (!is.null(phy$node.label)) phy$node.label <- phy$node.label[-(node2tip - Ntip)] - phy$tip.label <- new.tip.label - } else phy$tip.label <- phy$tip.label[-tip] - - ## update node.label if needed: - if (!is.null(phy$node.label)) - phy$node.label <- phy$node.label[sort(unique(phy$edge[, 1])) - Ntip] + phy$tip.label <- c(phy$tip.label, new.tip.label) + } phy$Nnode <- dim(phy$edge)[1] - n + 1L # update phy$Nnode ## The block below renumbers the nodes so that they conform - ## to the "phylo" format -- same as in root() + ## to the "phylo" format, same as in root() newNb <- integer(n + phy$Nnode) newNb[NEWROOT] <- n + 1L sndcol <- phy$edge[, 2] > n @@ -220,5 +220,10 @@ drop.tip <- (n + 2):(n + phy$Nnode) phy$edge[, 1] <- newNb[phy$edge[, 1]] storage.mode(phy$edge) <- "integer" + if (!is.null(phy$node.label)) { # update node.label if needed + newNb[is.na(newNb)] <- 0L + phy$node.label <- phy$node.label[order(newNb[newNb > 0])] + } collapse.singles(phy) } +