]> git.donarmstrong.com Git - ape.git/blobdiff - R/plot.phylo.R
various changes...
[ape.git] / R / plot.phylo.R
index 7798d286d0c5b395efefdc554979226d21d416f6..e02ba3071726ffcd8e87a6f966aff4e786bfa0eb 100644 (file)
@@ -1,8 +1,8 @@
-## plot.phylo.R (2009-10-27)
+## plot.phylo.R (2010-01-04)
 
 ##   Plot Phylogenies
 
-## Copyright 2002-2009 Emmanuel Paradis
+## Copyright 2002-2010 Emmanuel Paradis
 
 ## This file is part of the R-package `ape'.
 ## See the file ../COPYING for licensing issues.
@@ -62,12 +62,12 @@ plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
 
     phyloORclado <- type %in% c("phylogram", "cladogram")
     horizontal <- direction %in% c("rightwards", "leftwards")
+    xe <- x$edge # to save
     if (phyloORclado) {
         ## we first compute the y-coordinates of the tips.
         phyOrder <- attr(x, "order")
         ## make sure the tree is in cladewise order:
         if (is.null(phyOrder) || phyOrder != "cladewise") {
-            xe <- x$edge
             x <- reorder(x) # fix from Klaus Schliep (2007-06-16)
             if (!identical(x$edge, xe)) {
                 ## modified from Li-San Wang's fix (2007-01-23):
@@ -363,24 +363,17 @@ plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
             }
         }
         if (type %in% c("fan", "radial")) {
-            xx.scaled <- xx[1:Ntip]
-            if (type == "fan") { # no need if type == "radial"
-                maxx <- max(abs(xx.scaled))
-                if (maxx > 1) xx.scaled <- xx.scaled/maxx
-            }
-            angle <- acos(xx.scaled)*180/pi
-            s1 <- angle > 90 & yy[1:Ntip] > 0
-            s2 <- angle < 90 & yy[1:Ntip] < 0
-            s3 <- angle > 90 & yy[1:Ntip] < 0
-            angle[s1] <- angle[s1] + 180
-            angle[s2] <- -angle[s2]
-            angle[s3] <- 180 - angle[s3]
+            xx.tips <- xx[1:Ntip]
+            ## using atan2 considerably facilitates things compared to acos...
+            angle <- atan2(yy[1:Ntip], xx.tips)*180/pi
+            s <- xx.tips < 0
+            angle[s] <- angle[s] + 180
             adj <- numeric(Ntip)
-            adj[xx[1:Ntip] < 0] <- 1
+            adj[xx.tips < 0] <- 1
             ## `srt' takes only a single value, so can't vectorize this:
             for (i in 1:Ntip)
-              text(xx[i], yy[i], x$tip.label[i], font = font, cex = cex,
-                   srt = angle[i], adj = adj[i], col = tip.color[i])
+                text(xx[i], yy[i], x$tip.label[i], font = font, cex = cex,
+                     srt = angle[i], adj = adj[i], col = tip.color[i])
         }
     }
     if (show.node.label)
@@ -393,7 +386,7 @@ plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
               label.offset = label.offset, x.lim = x.lim, y.lim = y.lim,
               direction = direction, tip.color = tip.color,
               Ntip = Ntip, Nnode = Nnode)
-    assign("last_plot.phylo", c(L, list(edge = x$edge, xx = xx, yy = yy)),
+    assign("last_plot.phylo", c(L, list(edge = xe, xx = xx, yy = yy)),
            envir = .PlotPhyloEnv)
     invisible(L)
 }