]> git.donarmstrong.com Git - ape.git/commitdiff
added edge.lty to plot.phylo
authorparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Fri, 27 Mar 2009 10:20:14 +0000 (10:20 +0000)
committerparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Fri, 27 Mar 2009 10:20:14 +0000 (10:20 +0000)
git-svn-id: https://svn.mpl.ird.fr/ape/dev/ape@68 6e262413-ae40-0410-9e79-b911bd7a66b7

ChangeLog
DESCRIPTION
R/plot.phylo.R
man/plot.phylo.Rd
man/rotate.Rd

index 34d2b12d350462def15e6baed66599651a7e62ed..a32f0f85000533f0a45e9b61985d41a600a77391 100644 (file)
--- a/ChangeLog
+++ b/ChangeLog
@@ -14,7 +14,10 @@ NEW FEATURES
       labels in a flexible way.
 
     o read.tree() and write.tree() have been modified so that they can
-      handle individual tree names
+      handle individual tree names.
+
+    o plot.phylo() has a new argument 'edge.lty' that specifies the
+      types of lines used for the edges (plain, dotted, dashed, ...)
 
 
 BUG FIXES
index 94a1c6f262943e0f1fe44b2b0fa1e412567ec068..bcf5e6810b88860d6b5a6a47eae6f85aacf26608 100644 (file)
@@ -1,6 +1,6 @@
 Package: ape
 Version: 2.3
-Date: 2009-03-23
+Date: 2009-03-27
 Title: Analyses of Phylogenetics and Evolution
 Author: Emmanuel Paradis,
 Ben Bolker,
index ca3ff1ce570960fa9c86b35f0cdc93a146312da2..fe4543295491c5723a800fe43e77b86f2783c449 100644 (file)
@@ -1,8 +1,8 @@
-## plot.phylo.R (2008-05-08)
+## plot.phylo.R (2009-03-27)
 
 ##   Plot Phylogenies
 
-## Copyright 2002-2008 Emmanuel Paradis
+## Copyright 2002-2009 Emmanuel Paradis
 
 ## This file is part of the R-package `ape'.
 ## See the file ../COPYING for licensing issues.
@@ -10,7 +10,7 @@
 plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
                        node.pos = NULL, show.tip.label = TRUE,
                        show.node.label = FALSE, edge.color = "black",
-                       edge.width = 1, font = 3, cex = par("cex"),
+                       edge.width = 1, edge.lty = 1, font = 3, cex = par("cex"),
                        adj = NULL, srt = 0, no.margin = FALSE,
                        root.edge = FALSE, label.offset = 0, underscore = FALSE,
                        x.lim = NULL, y.lim = NULL, direction = "rightwards",
@@ -44,6 +44,7 @@ plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
     }
     edge.color <- rep(edge.color, length.out = Nedge)
     edge.width <- rep(edge.width, length.out = Nedge)
+    edge.lty <- rep(edge.lty, length.out = Nedge)
     ## fix from Li-San Wang (2007-01-23):
     xe <- x$edge
     x <- reorder(x, order = "pruningwise")
@@ -277,13 +278,13 @@ plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
     }
     if (type == "phylogram") {
         phylogram.plot(x$edge, Ntip, Nnode, xx, yy,
-                       horizontal, edge.color, edge.width)
+                       horizontal, edge.color, edge.width, edge.lty)
     } else {
       if (type == "fan")
         circular.plot(x$edge, Ntip, Nnode, xx, yy, theta,
-                      r, edge.color, edge.width)
+                      r, edge.color, edge.width, edge.lty)
       else
-        cladogram.plot(x$edge, xx, yy, edge.color, edge.width)
+        cladogram.plot(x$edge, xx, yy, edge.color, edge.width, edge.lty)
     }
     if (root.edge)
       switch(direction,
@@ -362,8 +363,8 @@ plot.phylo <- function(x, type = "phylogram", use.edge.length = TRUE,
     invisible(L)
 }
 
-phylogram.plot <- function(edge, Ntip, Nnode, xx, yy,
-                           horizontal, edge.color, edge.width)
+phylogram.plot <- function(edge, Ntip, Nnode, xx, yy, horizontal,
+                           edge.color, edge.width, edge.lty)
 {
     nodes <- (Ntip + 1):(Ntip + Nnode)
     if (!horizontal) {
@@ -390,46 +391,42 @@ phylogram.plot <- function(edge, Ntip, Nnode, xx, yy,
     pos <- match(sq, edge[, 2])
     x0h <- xx[edge[pos, 1]]
 
-    e.w <- unique(edge.width)
-    if (length(e.w) == 1) width.v <- rep(e.w, Nnode)
-    else {
-        width.v <- rep(1, Nnode)
-        for (i in 1:Nnode) {
-            br <- edge[which(edge[, 1] == i + Ntip), 2]
-            width <- unique(edge.width[br])
-            if (length(width) == 1) width.v[i] <- width
-        }
-    }
-    e.c <- unique(edge.color)
-    if (length(e.c) == 1) color.v <- rep(e.c, Nnode)
-    else {
-        color.v <- rep("black", Nnode)
-        for (i in 1:Nnode) {
-            br <- which(edge[, 1] == i + Ntip)
-            #br <- edge[which(edge[, 1] == i + Ntip), 2]
-            color <- unique(edge.color[br])
-            if (length(color) == 1) color.v[i] <- color
+    ## function dispatching the features to the vertical edges
+    foo <- function(edge.feat, default) {
+        e <- unique(edge.feat)
+        if (length(e) == 1) return(rep(e, Nnode)) else {
+            feat.v <- rep(default, Nnode)
+            for (i in 1:Nnode) {
+                br <- which(edge[, 1] == i + Ntip)
+                x <- unique(edge.feat[br])
+                if (length(x) == 1) feat.v[i] <- x
+            }
         }
+        feat.v
     }
+    color.v <- foo(edge.color, "black")
+    width.v <- foo(edge.width, 1)
+    lty.v <- foo(edge.lty, 1)
 
-    ## we need to reorder `edge.color' and `edge.width':
+    ## we need to reorder:
     edge.width <- edge.width[pos]
     edge.color <- edge.color[pos]
+    edge.lty <- edge.lty[pos]
     if (horizontal) {
-        segments(x0v, y0v, x0v, y1v, col = color.v, lwd = width.v) # draws vertical lines
-        segments(x0h, y0h, x1h, y0h, col = edge.color, lwd = edge.width) # draws horizontal lines
+        segments(x0v, y0v, x0v, y1v, col = color.v, lwd = width.v, lty = lty.v) # draws vertical lines
+        segments(x0h, y0h, x1h, y0h, col = edge.color, lwd = edge.width, lty = edge.lty) # draws horizontal lines
     } else {
-        segments(y0v, x0v, y1v, x0v, col = color.v, lwd = width.v) # draws horizontal lines
-        segments(y0h, x0h, y0h, x1h, col = edge.color, lwd = edge.width) # draws vertical lines
+        segments(y0v, x0v, y1v, x0v, col = color.v, lwd = width.v, lty = lty.v) # draws horizontal lines
+        segments(y0h, x0h, y0h, x1h, col = edge.color, lwd = edge.width, lty = edge.lty) # draws vertical lines
     }
 }
 
-cladogram.plot <- function(edge, xx, yy, edge.color, edge.width)
+cladogram.plot <- function(edge, xx, yy, edge.color, edge.width, edge.lty)
   segments(xx[edge[, 1]], yy[edge[, 1]], xx[edge[, 2]], yy[edge[, 2]],
-           col = edge.color, lwd = edge.width)
+           col = edge.color, lwd = edge.width, lty = edge.lty)
 
 circular.plot <- function(edge, Ntip, Nnode, xx, yy, theta,
-                          r, edge.color, edge.width)
+                          r, edge.color, edge.width, edge.lty)
 {
     r0 <- r[edge[, 1]]
     r1 <- r[edge[, 2]]
@@ -440,7 +437,7 @@ circular.plot <- function(edge, Ntip, Nnode, xx, yy, theta,
     x1 <- r1*cos(theta0)
     y1 <- r1*sin(theta0)
 
-    segments(x0, y0, x1, y1, col = edge.color, lwd = edge.width)
+    segments(x0, y0, x1, y1, col = edge.color, lwd = edge.width, lty = edge.lty)
 
     tmp <- which(diff(edge[, 1]) != 0)
     start <- c(1, tmp + 1)
@@ -453,7 +450,8 @@ circular.plot <- function(edge, Ntip, Nnode, xx, yy, theta,
         Y <- seq(theta[edge[i, 2]], theta[edge[j, 2]], length.out = 100)
         co <- if (edge.color[i] == edge.color[j]) edge.color[i] else "black"
         lw <- if (edge.width[i] == edge.width[j]) edge.width[i] else 1
-        lines(X*cos(Y), X*sin(Y), col = co, lwd = lw)
+        ly <- if (edge.lty[i] == edge.lty[j]) edge.lty[i] else 1
+        lines(X*cos(Y), X*sin(Y), col = co, lwd = lw, lty = ly)
     }
 }
 
index dcabb28e6abdc8e90bdbf0c5fc1117e4c3481376..ba98021ef7374fc5ee5199024f47960293b3210d 100644 (file)
@@ -5,7 +5,7 @@
 \usage{
 \method{plot}{phylo}(x, type = "phylogram", use.edge.length = TRUE,
     node.pos = NULL, show.tip.label = TRUE, show.node.label = FALSE,
-    edge.color = "black", edge.width = 1, font = 3,
+    edge.color = "black", edge.width = 1, edge.lty = 1, font = 3,
     cex = par("cex"), adj = NULL, srt = 0, no.margin = FALSE,
     root.edge = FALSE, label.offset = 0, underscore = FALSE,
     x.lim = NULL, y.lim = NULL, direction = "rightwards",
@@ -42,6 +42,8 @@
     the plotted phylogeny. These are taken to be in the same order than
     the component \code{edge} of \code{phy}. If fewer widths are given
     than the length of \code{edge}, then these are recycled.}
+  \item{edge.lty}{same than the previous argument but for line types;
+    1: plain, 2: dashed, 3: dotted, 4: dotdash, 5: longdash, 6: twodash.}
   \item{font}{an integer specifying the type of font for the labels: 1
     (plain text), 2 (bold), 3 (italic, the default), or 4 (bold
     italic).}
index 13fed062b35f910525cdcc33204ed76f3b32d7c4..850247a28cf4675f29b9b389efed8a8c5095b9d0 100644 (file)
@@ -1,6 +1,6 @@
 \name{rotate}
 \alias{rotate}
-\title{Swopping sister clades}
+\title{Swapping sister clades}
 \description{
 For a given node, rotate exchanges the position of two clades descending from this node. It can handle dichotomies as well as polytomies. In the latter case, two clades from the polytomy are selected for swapping.}
 \usage{