]> git.donarmstrong.com Git - ape.git/blobdiff - R/plot.phylo.R
bug corrected in del.gaps + small change in man page of theta.s
[ape.git] / R / plot.phylo.R
index 76a1d6babac0945e2b83e5a4cda86efc88e0eb6c..ca3ff1ce570960fa9c86b35f0cdc93a146312da2 100644 (file)
@@ -1,8 +1,8 @@
-## plot.phylo.R (2007-12-22)
+## plot.phylo.R (2008-05-08)
 
 ##   Plot Phylogenies
 
-## Copyright 2002-2007 Emmanuel Paradis
+## Copyright 2002-2008 Emmanuel Paradis
 
 ## This file is part of the R-package `ape'.
 ## See the file ../COPYING for licensing issues.
@@ -245,9 +245,10 @@ plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
         if (direction == "leftwards") x.lim[2] <- x.lim[2] + x$root.edge
         if (direction == "downwards") y.lim[2] <- y.lim[2] + x$root.edge
     }
-
+    ## fix by Klaus Schliep (2008-03-28):
+    asp <- if (type %in% c("fan", "radial")) 1 else NA
     plot(0, type = "n", xlim = x.lim, ylim = y.lim, xlab = "",
-         ylab = "", xaxt = "n", yaxt = "n", bty = "n", ...)
+         ylab = "", xaxt = "n", yaxt = "n", bty = "n", asp = asp, ...)
     if (is.null(adj))
       adj <- if (phyloORclado && direction == "leftwards") 1 else 0
     if (phyloORclado) {
@@ -328,7 +329,7 @@ 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(xx.scaled)
+                maxx <- max(abs(xx.scaled))
                 if (maxx > 1) xx.scaled <- xx.scaled/maxx
             }
             angle <- acos(xx.scaled)*180/pi
@@ -356,7 +357,8 @@ 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)
-    .last_plot.phylo <<- c(L, list(edge = xe, xx = xx, yy = yy))
+    assign("last_plot.phylo", c(L, list(edge = xe, xx = xx, yy = yy)),
+           envir = .PlotPhyloEnv)
     invisible(L)
 }
 
@@ -509,9 +511,10 @@ plot.multiPhylo <- function(x, layout = 1, ...)
 {
     if (layout > 1)
       layout(matrix(1:layout, ceiling(sqrt(layout)), byrow = TRUE))
+    else layout(matrix(1))
     if (!par("ask")) {
         par(ask = TRUE)
         on.exit(par(ask = FALSE))
     }
-    for (i in x) plot(i, ...)
+    for (i in 1:length(x)) plot(x[[i]], ...)
 }