]> git.donarmstrong.com Git - ape.git/blobdiff - R/nodelabels.R
fixing nj() with many 0 distances
[ape.git] / R / nodelabels.R
index 0b735971d414150d87125a975e7993a4d4845277..43ffb93a55da2db56eb8c037b84a4f6d5c3ffc4d 100644 (file)
@@ -1,4 +1,4 @@
-## nodelabels.R (2008-02-21)
+## nodelabels.R (2008-02-28)
 
 ##   Labelling Trees
 
@@ -120,13 +120,10 @@ nodelabels <- function(text, node, adj = c(0.5, 0.5), frame = "rect",
                        pch = NULL, thermo = NULL, pie = NULL, piecol = NULL,
                        col = "black", bg = "lightblue", ...)
 {
-    xx <- get("last_plot.phylo$xx", envir = .PlotPhyloEnv)
-    yy <- get("last_plot.phylo$yy", envir = .PlotPhyloEnv)
-    if (missing(node))
-        node <- (get("last_plot.phylo$Ntip",
-                     envir = .PlotPhyloEnv) + 1):length(xx)
-    XX <- xx[node]
-    YY <- yy[node]
+    lastPP <- get("last_plot.phylo", envir = .PlotPhyloEnv)
+    if (missing(node)) node <- (lastPP$Ntip + 1):length(lastPP$xx)
+    XX <- lastPP$xx[node]
+    YY <- lastPP$yy[node]
     BOTHlabels(text, node, XX, YY, adj, frame, pch, thermo,
                pie, piecol, col, bg, ...)
 }
@@ -135,10 +132,10 @@ tiplabels <- function(text, tip, adj = c(0.5, 0.5), frame = "rect",
                       pch = NULL, thermo = NULL, pie = NULL, piecol = NULL,
                       col = "black", bg = "yellow", ...)
 {
-    if (missing(tip))
-        tip <- 1:get("last_plot.phylo$Ntip", envir = .PlotPhyloEnv)
-    XX <- get("last_plot.phylo$xx", envir = .PlotPhyloEnv)[tip]
-    YY <- get("last_plot.phylo$yy", envir = .PlotPhyloEnv)[tip]
+    lastPP <- get("last_plot.phylo", envir = .PlotPhyloEnv)
+    if (missing(tip)) tip <- 1:lastPP$Ntip
+    XX <- lastPP$xx[tip]
+    YY <- lastPP$yy[tip]
     BOTHlabels(text, tip, XX, YY, adj, frame, pch, thermo,
                pie, piecol, col, bg, ...)
 }
@@ -147,28 +144,25 @@ edgelabels <- function(text, edge, adj = c(0.5, 0.5), frame = "rect",
                       pch = NULL, thermo = NULL, pie = NULL, piecol = NULL,
                       col = "black", bg = "lightgreen", ...)
 {
-    xx <- get("last_plot.phylo$xx", envir = .PlotPhyloEnv)
-    yy <- get("last_plot.phylo$yy", envir = .PlotPhyloEnv)
-    lastEdge <- get("last_plot.phylo$edge", envir = .PlotPhyloEnv)
+    lastPP <- get("last_plot.phylo", envir = .PlotPhyloEnv)
     if (missing(edge)) {
-        sel <- 1:dim(lastEdge)[1]
-        subedge <- lastEdge
+        sel <- 1:dim(lastPP$edge)[1]
+        subedge <- lastPP$edge
     } else {
         sel <- edge
-        subedge <- lastEdge[sel, , drop = FALSE]
+        subedge <- lastPP$edge[sel, , drop = FALSE]
     }
-    if (get("last_plot.phylo$type", envir = .PlotPhyloEnv) == "phylogram") {
-        if(get("last_plot.phylo$direction", envir = .PlotPhyloEnv)
-           %in% c("rightwards", "leftwards")) {
-            XX <- (xx[subedge[, 1]] + xx[subedge[, 2]]) / 2
-            YY <- yy[subedge[, 2]]
+    if (lastPP$type == "phylogram") {
+        if (lastPP$direction %in% c("rightwards", "leftwards")) {
+            XX <- (lastPP$xx[subedge[, 1]] + lastPP$xx[subedge[, 2]]) / 2
+            YY <- lastPP$yy[subedge[, 2]]
         } else {
-            XX <- xx[subedge[, 2]]
-            YY <- (yy[subedge[, 1]] + yy[subedge[, 2]]) / 2
+            XX <- lastPP$xx[subedge[, 2]]
+            YY <- (lastPP$yy[subedge[, 1]] + lastPP$yy[subedge[, 2]]) / 2
         }
     } else {
-        XX <- (xx[subedge[, 1]] + xx[subedge[, 2]]) / 2
-        YY <- (yy[subedge[, 1]] + yy[subedge[, 2]]) / 2
+        XX <- (lastPP$xx[subedge[, 1]] + lastPP$xx[subedge[, 2]]) / 2
+        YY <- (lastPP$yy[subedge[, 1]] + lastPP$yy[subedge[, 2]]) / 2
     }
     BOTHlabels(text, sel, XX, YY, adj, frame, pch, thermo,
                pie, piecol, col, bg, ...)