X-Git-Url: https://git.donarmstrong.com/?a=blobdiff_plain;f=R%2Fdrop.tip.R;h=c5eb07c45c728d381830ff3761c165c4f9e329be;hb=50470fdeb74ae1e235e61ed6acfae81dd51f655c;hp=acdbe688d7643f6465b9d04c5a30844ce027ffea;hpb=767a9ed6bc4444aac3dc1a26a91fc3986e99665c;p=ape.git diff --git a/R/drop.tip.R b/R/drop.tip.R index acdbe68..c5eb07c 100644 --- a/R/drop.tip.R +++ b/R/drop.tip.R @@ -1,29 +1,31 @@ -## drop.tip.R (2009-07-06) +## drop.tip.R (2010-07-21) ## Remove Tips in a Phylogenetic Tree -## Copyright 2003-2009 Emmanuel Paradis +## Copyright 2003-2010 Emmanuel Paradis ## This file is part of the R-package `ape'. ## See the file ../COPYING for licensing issues. -extract.clade <- function(phy, node, root.edge = 0) +extract.clade <- function(phy, node, root.edge = 0, interactive = FALSE) { Ntip <- length(phy$tip.label) ROOT <- Ntip + 1 Nedge <- dim(phy$edge)[1] wbl <- !is.null(phy$edge.length) - if (length(node) > 1) { - node <- node[1] - warning("only the first value of 'node' has been considered") - } - if (is.character(node)) { - if (is.null(phy$node.label)) - stop("the tree has no node labels") - node <- which(phy$node.label %in% node) + Ntip + if (interactive) node <- identify(phy)$nodes else { + if (length(node) > 1) { + node <- node[1] + warning("only the first value of 'node' has been considered") + } + if (is.character(node)) { + if (is.null(phy$node.label)) + stop("the tree has no node labels") + node <- which(phy$node.label %in% node) + Ntip + } + if (node <= Ntip) + stop("node number must be greater than the number of tips") } - if (node <= Ntip) - stop("node number must be greater than the number of tips") if (node == ROOT) return(phy) phy <- reorder(phy) # insure it is in cladewise order root.node <- which(phy$edge[, 2] == node) @@ -52,7 +54,7 @@ extract.clade <- function(phy, node, root.edge = 0) 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] + phy$tip.label <- phy$tip.label[sort(tip)] # <- added sort to avoid shuffling of tip labels (2010-07-21) ## keep the ordering so no need to reorder tip.label: phy$edge[TIPS, 2] <- order(tip) if (!is.null(phy$node.label)) @@ -73,15 +75,27 @@ extract.clade <- function(phy, node, root.edge = 0) drop.tip <- function(phy, tip, trim.internal = TRUE, subtree = FALSE, - root.edge = 0, rooted = is.rooted(phy)) + root.edge = 0, rooted = is.rooted(phy), interactive = FALSE) { if (!inherits(phy, "phylo")) stop('object "phy" is not of class "phylo"') Ntip <- length(phy$tip.label) ## find the tips to drop: - if (is.character(tip)) - tip <- which(phy$tip.label %in% tip) + if (interactive) { + cat("Left-click close to the tips you want to drop; right-click when finished...\n") + xy <- locator() + nToDrop <- length(xy$x) + tip <- integer(nToDrop) + lastPP <- get("last_plot.phylo", envir = .PlotPhyloEnv) + for (i in 1:nToDrop) { + d <- sqrt((xy$x[i] - lastPP$xx)^2 + (xy$y[i] - lastPP$yy)^2) + tip[i] <- which.min(d) + } + } else { + if (is.character(tip)) + tip <- which(phy$tip.label %in% tip) + } if (!rooted && subtree) { phy <- root(phy, (1:Ntip)[-tip][1]) @@ -167,8 +181,9 @@ drop.tip <- n <- length(oldNo.ofNewTips) # the new number of tips in the tree - ## assumes that the ordering of tips is unchanged: - phy$edge[TERMS, 2] <- 1:n + ## the tips may not be sorted in increasing order of their + ## in the 2nd col of edge, so no need to reorder $tip.label + phy$edge[TERMS, 2] <- rank(phy$edge[TERMS, 2]) ## make new tip labels if necessary: if (subtree || !trim.internal) {