]> git.donarmstrong.com Git - ape.git/commitdiff
new files by Damien + a few bug fixes
authorparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Thu, 17 Apr 2008 12:46:51 +0000 (12:46 +0000)
committerparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Thu, 17 Apr 2008 12:46:51 +0000 (12:46 +0000)
git-svn-id: https://svn.mpl.ird.fr/ape/dev/ape@25 6e262413-ae40-0410-9e79-b911bd7a66b7

Changes
DESCRIPTION
R/plot.cophylo.R [new file with mode: 0644]
R/plot.phylo.coor.R [new file with mode: 0644]
R/subtreeplot.R [new file with mode: 0644]
R/subtrees.R [new file with mode: 0644]
R/zoom.R
Thanks
man/plot.cophylo.Rd [new file with mode: 0644]
man/subtreeplot.Rd [new file with mode: 0644]
man/subtrees.Rd [new file with mode: 0644]

diff --git a/Changes b/Changes
index 19e350a2dbedeb0bffbc50a9ac0eb2fb17394c58..5199d0153eccf02a758881377bcc7540844c797b 100644 (file)
--- a/Changes
+++ b/Changes
@@ -1,6 +1,14 @@
                CHANGES IN APE VERSION 2.1-4
 
 
+NEW FEATURES
+
+    o Four new functions have been written by Damien de Vienne for the
+      graphical exploration of large trees (plot.cophylo, subtrees,
+      subtreeplot), and to return the graphical coordinates of tree
+      (without plotting).
+
+
 BUG FIXES
 
     o read.dna() failed if "?" occurred in the first 10 sites of the
@@ -12,6 +20,9 @@ BUG FIXES
     o Drawing the tip labels sometimes failed when plotting circular
       trees.
 
+    o zoom() failed when tip labels were used instead of their numbers
+      (thanks to Yan Wong for the fix).
+
 
 OTHER CHANGES
 
index d3be1eb48bd0fdd7536c6dfa93be670033e88d7a..510eef47806c3244795109bc17c91057a7156f64 100644 (file)
@@ -1,11 +1,12 @@
 Package: ape
 Version: 2.1-4
-Date: 2008-03-28
+Date: 2008-04-17
 Title: Analyses of Phylogenetics and Evolution
 Author: Emmanuel Paradis, Ben Bolker, Julien Claude, Hoa Sien Cuong,
   Richard Desper, Benoit Durand, Julien Dutheil, Olivier Gascuel,
   Gangolf Jobb, Christoph Heibl, Vincent Lefort, Jim Lemon,
-  Yvonnick Noel, Johan Nylander, Rainer Opgen-Rhein, Korbinian Strimmer
+  Yvonnick Noel, Johan Nylander, Rainer Opgen-Rhein, Korbinian Strimmer,
+  Damien de Vienne
 Maintainer: Emmanuel Paradis <Emmanuel.Paradis@mpl.ird.fr>
 Depends: R (>= 2.6.0)
 Suggests: gee, nlme, lattice
diff --git a/R/plot.cophylo.R b/R/plot.cophylo.R
new file mode 100644 (file)
index 0000000..7589f6a
--- /dev/null
@@ -0,0 +1,173 @@
+## plot.cophylo.R (2008-04-14)
+
+##   Plots two phylogenetic trees face to
+##   face with the links between the tips
+
+## Copyright 2008 Damien de Vienne
+
+## This file is part of the R-package `ape'.
+## See the file ../COPYING for licensing issues.
+
+plot.cophylo <-
+    function (x, y, assoc = NULL, use.edge.length = FALSE, space = 0,
+              length.line = 1, gap = 2, type = "phylogram",
+              rotate = FALSE, col = "red", show.tip.label = TRUE,
+              font = 3)
+{
+    if (is.null(assoc)) {
+        assoc <- matrix(ncol = 2)
+        print("No association matrix specified. Links will be omitted.")
+    }
+    if (rotate == TRUE) {
+        cat("\n    Click on a node to rotate (right click to exit)\n\n")
+        repeat {
+            res <- plot.cophylo2(x, y, assoc = assoc, use.edge.length = use.edge.length,
+                space = space, length.line = length.line, gap = gap,
+                type = type, return = TRUE, col = col, show.tip.label = show.tip.label,
+                font = font)
+            click <- identify(res$c[, 1], res$c[, 2], n = 1)
+            if (click < length(res$a[, 1]) + 1) {
+                if (click > res$N.tip.x)
+                  x <- rotate(x, click)
+            }
+            else if (click < length(res$c[, 1]) + 1) {
+                if (click > length(res$a[, 1]) + res$N.tip.y)
+                  y <- rotate(y, click - length(res$a[, 1]))
+            }
+            plot.cophylo2(x, y, assoc = assoc, use.edge.length = use.edge.length,
+                space = space, length.line = length.line, gap = gap,
+                type = type, return = TRUE, col = col, show.tip.label = show.tip.label,
+                font = font)
+        }
+        on.exit(print("done"))
+    }
+    else plot.cophylo2(x, y, assoc = assoc, use.edge.length = use.edge.length,
+        space = space, length.line = length.line, gap = gap,
+        type = type, return = FALSE, col = col, show.tip.label = show.tip.label,
+        font = font)
+}
+
+plot.cophylo2 <-
+    function (x, y, assoc = assoc, use.edge.length = use.edge.length,
+              space = space, length.line = length.line, gap = gap,
+              type = type, return = return, col = col,
+              show.tip.label = show.tip.label, font = font)
+{
+    res <- list()
+
+###choice of the minimum space between the trees###
+    left <- max(nchar(x$tip.label, type = "width")) + length.line
+    right <- max(nchar(y$tip.label, type = "width")) + length.line
+    space.min <- left + right + gap * 2
+    if ((space <= 0) || (space < space.min))
+        space <- space.min
+
+    N.tip.x <- Ntip(x)
+    N.tip.y <- Ntip(y)
+    res$N.tip.x <- N.tip.x
+    res$N.tip.y <- N.tip.y
+    a <- plot.phylo.coor(x, use.edge.length = use.edge.length,
+        type = type)
+    res$a <- a
+    b <- plot.phylo.coor(y, use.edge.length = use.edge.length,
+        direction = "leftwards", type = type)
+
+###for the two trees to have the extreme leaves at the same ordinate.
+    a[, 2] <- a[, 2] - min(a[, 2])
+    b[, 2] <- b[, 2] - min(b[, 2])
+
+    res$b <- b
+
+    b2 <- b
+    b2[, 1] <- b[1:nrow(b), 1] * (max(a[, 1])/max(b[, 1])) +
+        space + max(a[, 1])
+    b2[, 2] <- b[1:nrow(b), 2] * (max(a[, 2])/max(b[, 2]))
+
+    res$b2 <- b2
+
+    c <- matrix(ncol = 2, nrow = nrow(a) + nrow(b))
+    c[1:nrow(a), ] <- a[1:nrow(a), ]
+    c[nrow(a) + 1:nrow(b), 1] <- b2[, 1]
+    c[nrow(a) + 1:nrow(b), 2] <- b2[, 2]
+    res$c <- c
+
+    plot(c, type = "n", xlim = NULL, ylim = NULL, log = "", main = NULL,
+         sub = NULL, xlab = NULL, ylab = NULL, ann = FALSE, axes = FALSE,
+         frame.plot = FALSE)
+
+###segments for cladograms
+    if (type == "cladogram") {
+        for (i in 1:(nrow(a) - 1))
+            segments(a[x$edge[i, 1], 1], a[x$edge[i, 1], 2],
+                     a[x$edge[i, 2], 1], a[x$edge[i, 2], 2])
+        for (i in 1:(nrow(b) - 1))
+            segments(b2[y$edge[i, 1], 1], b2[y$edge[i, 1], 2],
+                     b2[y$edge[i, 2], 1], b2[y$edge[i, 2], 2])
+    }
+
+###segments for phylograms
+    if (type == "phylogram") {
+        for (i in (N.tip.x + 1):nrow(a)) {
+            l <- length(x$edge[x$edge[, 1] == i, ][, 1])
+            for (j in 1:l) {
+                segments(a[x$edge[x$edge[, 1] == i, ][1, 1],
+                  1], a[x$edge[x$edge[, 1] == i, 2], 2][1], a[x$edge[x$edge[,
+                  1] == i, ][1, 1], 1], a[x$edge[x$edge[, 1] ==
+                  i, 2], 2][j])
+                segments(a[x$edge[x$edge[, 1] == i, ][1, 1],
+                  1], a[x$edge[x$edge[, 1] == i, 2], 2][j], a[x$edge[x$edge[,
+                  1] == i, 2], 1][j], a[x$edge[x$edge[, 1] ==
+                  i, 2], 2][j])
+            }
+        }
+        for (i in (N.tip.y + 1):nrow(b)) {
+            l <- length(y$edge[y$edge[, 1] == i, ][, 1])
+            for (j in 1:l) {
+                segments(b2[y$edge[y$edge[, 1] == i, ][1, 1],
+                  1], b2[y$edge[y$edge[, 1] == i, 2], 2][1],
+                  b2[y$edge[y$edge[, 1] == i, ][1, 1], 1], b2[y$edge[y$edge[,
+                    1] == i, 2], 2][j])
+                segments(b2[y$edge[y$edge[, 1] == i, ][1, 1],
+                  1], b2[y$edge[y$edge[, 1] == i, 2], 2][j],
+                  b2[y$edge[y$edge[, 1] == i, 2], 1][j], b2[y$edge[y$edge[,
+                    1] == i, 2], 2][j])
+            }
+        }
+    }
+    if (show.tip.label) {
+        text(a[1:N.tip.x, ], cex = 0, font = font, pos = 4,
+             labels = x$tip.label)
+        text(b2[1:N.tip.y, ], cex = 1, font = font, pos = 2,
+            labels = y$tip.label)
+    }
+
+###links between associated taxa. Takes into account the size of the character strings of the taxa names.
+    lsa <- 1:N.tip.x
+    lsb <- 1:N.tip.y
+    decx <- array(nrow(assoc))
+    decy <- array(nrow(assoc))
+    for (i in 1:nrow(assoc)) {
+        if (show.tip.label) {
+            decx[i] <- strwidth(x$tip.label[lsa[x$tip.label ==
+                assoc[i, 1]]])
+            decy[i] <- strwidth(y$tip.label[lsb[y$tip.label ==
+                assoc[i, 1]]])
+        } else {
+            decx[i] <- decy[i] <- 0
+        }
+        segments(a[lsa[x$tip.label == assoc[i, 1]], 1] + decx[i] +
+            gap, a[lsa[x$tip.label == assoc[i, 1]], 2], a[lsa[x$tip.label ==
+            assoc[i, 1]], 1] + gap + left, a[lsa[x$tip.label ==
+            assoc[i, 1]], 2], col = col)
+        segments(b2[lsb[y$tip.label == assoc[i, 2]], 1] - (decy[i] +
+            gap), b2[lsb[y$tip.label == assoc[i, 2]], 2], b2[lsb[y$tip.label ==
+            assoc[i, 2]], 1] - (gap + right), b2[lsb[y$tip.label ==
+            assoc[i, 2]], 2], col = col)
+        segments(a[lsa[x$tip.label == assoc[i, 1]], 1] + gap +
+            left, a[lsa[x$tip.label == assoc[i, 1]], 2], b2[lsb[y$tip.label ==
+            assoc[i, 2]], 1] - (gap + right), b2[lsb[y$tip.label ==
+            assoc[i, 2]], 2], col = col)
+    }
+    if (return == TRUE)
+        return(res)
+}
diff --git a/R/plot.phylo.coor.R b/R/plot.phylo.coor.R
new file mode 100644 (file)
index 0000000..b69fb95
--- /dev/null
@@ -0,0 +1,134 @@
+## plot.phylo.coor.R (2008-04-14)
+
+##   Coordinates of a Tree Plot
+
+## Copyright 2008 Damien de Vienne
+
+## This file is part of the R-package `ape'.
+## See the file ../COPYING for licensing issues.
+
+plot.phylo.coor <-
+    function (x, type = "phylogram", use.edge.length = TRUE, node.pos = NULL,
+              direction = "rightwards")
+{
+    Ntip <- length(x$tip.label)
+    if (Ntip == 1)
+        stop("found only one tip in the tree!")
+    Nedge <- dim(x$edge)[1]
+    if (any(tabulate(x$edge[, 1]) == 1))
+        stop("there are single (non-splitting) nodes in your tree; you may need to use collapse.singles().")
+    Nnode <- x$Nnode
+    if (is.null(x$edge.length)) use.edge.length <- FALSE
+    phyloORclado <- type %in% c("phylogram", "cladogram")
+    horizontal <- direction %in% c("rightwards", "leftwards")
+    if (phyloORclado) {
+        if (!is.null(attr(x, "order")))
+            if (attr(x, "order") == "pruningwise")
+                x <- reorder(x)
+        yy <- numeric(Ntip + Nnode)
+        TIPS <- x$edge[x$edge[, 2] <= Ntip, 2]
+        yy[TIPS] <- 1:Ntip
+
+    }
+
+    xe <- x$edge
+    x <- reorder(x, order = "pruningwise")
+    ereorder <- match(x$edge[, 2], xe[, 2])
+
+    if (phyloORclado) {
+        if (is.null(node.pos)) {
+            node.pos <- 1
+            if (type == "cladogram" && !use.edge.length)
+                node.pos <- 2
+        }
+        if (node.pos == 1)
+            yy <- .C("node_height", as.integer(Ntip), as.integer(Nnode),
+                as.integer(x$edge[, 1]), as.integer(x$edge[,
+                  2]), as.integer(Nedge), as.double(yy), DUP = FALSE,
+                PACKAGE = "ape")[[6]]
+        else {
+            ans <- .C("node_height_clado", as.integer(Ntip),
+                as.integer(Nnode), as.integer(x$edge[, 1]), as.integer(x$edge[,
+                  2]), as.integer(Nedge), double(Ntip + Nnode),
+                as.double(yy), DUP = FALSE, PACKAGE = "ape")
+            xx <- ans[[6]] - 1
+            yy <- ans[[7]]
+        }
+        if (!use.edge.length) {
+            if (node.pos != 2)
+                xx <- .C("node_depth", as.integer(Ntip), as.integer(Nnode),
+                  as.integer(x$edge[, 1]), as.integer(x$edge[,
+                    2]), as.integer(Nedge), double(Ntip + Nnode),
+                  DUP = FALSE, PACKAGE = "ape")[[6]] - 1
+            xx <- max(xx) - xx
+        }
+        else {
+            xx <- .C("node_depth_edgelength", as.integer(Ntip),
+                as.integer(Nnode), as.integer(x$edge[, 1]), as.integer(x$edge[,
+                  2]), as.integer(Nedge), as.double(x$edge.length),
+                double(Ntip + Nnode), DUP = FALSE, PACKAGE = "ape")[[7]]
+        }
+    }
+    ##if (type == "fan") {
+    ##    TIPS <- xe[which(xe[, 2] <= Ntip), 2]
+    ##    xx <- seq(0, 2 * pi * (1 - 1/Ntip), 2 * pi/Ntip)
+    ##    theta <- double(Ntip)
+    ##    theta[TIPS] <- xx
+    ##    theta <- c(theta, numeric(Nnode))
+    ##    theta <- .C("node_height", as.integer(Ntip), as.integer(Nnode),
+    ##        as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
+    ##        as.integer(Nedge), theta, DUP = FALSE, PACKAGE = "ape")[[6]]
+    ##    if (use.edge.length) {
+    ##        r <- .C("node_depth_edgelength", as.integer(Ntip),
+    ##            as.integer(Nnode), as.integer(x$edge[, 1]), as.integer(x$edge[,
+    ##              2]), as.integer(Nedge), as.double(x$edge.length),
+    ##            double(Ntip + Nnode), DUP = FALSE, PACKAGE = "ape")[[7]]
+    ##    }
+    ##    else {
+    ##        r <- .C("node_depth", as.integer(Ntip), as.integer(Nnode),
+    ##            as.integer(x$edge[, 1]), as.integer(x$edge[,
+    ##              2]), as.integer(Nedge), double(Ntip + Nnode),
+    ##            DUP = FALSE, PACKAGE = "ape")[[6]]
+    ##        r <- 1/r
+    ##    }
+    ##    xx <- r * cos(theta)
+    ##    yy <- r * sin(theta)
+    ##}
+    ##if (type == "unrooted") {
+    ##    XY <- if (use.edge.length)
+    ##        unrooted.xy(Ntip, Nnode, x$edge, x$edge.length)
+    ##    else unrooted.xy(Ntip, Nnode, x$edge, rep(1, Nedge))
+    ##    xx <- XY$M[, 1] - min(XY$M[, 1])
+    ##    yy <- XY$M[, 2] - min(XY$M[, 2])
+    ##}
+    ##if (type == "radial") {
+    ##    X <- .C("node_depth", as.integer(Ntip), as.integer(Nnode),
+    ##        as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
+    ##        as.integer(Nedge), double(Ntip + Nnode), DUP = FALSE,
+    ##        PACKAGE = "ape")[[6]]
+    ##    X[X == 1] <- 0
+    ##    X <- 1 - X/Ntip
+    ##    yy <- c((1:Ntip) * 2 * pi/Ntip, rep(0, Nnode))
+    ##    Y <- .C("node_height", as.integer(Ntip), as.integer(Nnode),
+    ##        as.integer(x$edge[, 1]), as.integer(x$edge[, 2]),
+    ##        as.integer(Nedge), as.double(yy), DUP = FALSE, PACKAGE = "ape")[[6]]
+    ##    xx <- X * cos(Y)
+    ##    yy <- X * sin(Y)
+    ##}
+    if (phyloORclado && direction != "rightwards") {
+        if (direction == "leftwards") {
+            xx <- -xx
+            xx <- xx - min(xx)
+        }
+        if (!horizontal) {
+            tmp <- yy
+            yy <- xx
+            xx <- tmp - min(tmp) + 1
+            if (direction == "downwards") {
+                yy <- -yy
+                yy <- yy - min(yy)
+            }
+        }
+    }
+    cbind(xx, yy)
+}
diff --git a/R/subtreeplot.R b/R/subtreeplot.R
new file mode 100644 (file)
index 0000000..4e6f81f
--- /dev/null
@@ -0,0 +1,47 @@
+## subtreeplot.R (2008-04-14)
+
+##  Zoom on a Portion of a Phylogeny by Successive Clicks
+
+## Copyright 2008 Damien de Vienne
+
+## This file is part of the R-package `ape'.
+## See the file ../COPYING for licensing issues.
+
+subtreeplot<-function(x, wait=FALSE, ...) {
+
+    sub<-subtrees(x, wait=wait)
+    y<-NULL
+    plot.default(0, type="n",axes=FALSE, ann=FALSE)
+    repeat {
+         split.screen(c(1,2))
+        screen(2)
+        if (is.null(y)) plot(x,...)
+        else plot(y,sub=paste("Node :", click),...)
+        screen(1)
+        plot(x,sub="Complete tree",main="Type ESC or right click to exit", cex.main=0.9, ...)
+
+        N.tip<-Ntip(x)
+        N.node<-Nnode(x)
+
+        coor<-plot.phylo.coor(x)
+        tips<-x$tip.label
+        nodes<-x$node.label
+        if (is.null(x$node.label)) nodes<-(N.tip+1):(N.tip+N.node)
+        labs<-c(rep("",N.tip), nodes)
+
+        click<-identify(coor[,1], coor[,2], labels=labs, n=1)
+        if (length(click) == 0) {return(y)}
+        if (click > N.tip) {
+            close.screen(c(1,2),all.screens = TRUE)
+            split.screen(c(1,2))
+            screen(1) #selects the screen to plot in
+            plot(x, sub="Complete tree", ...) # plots x in screen 1 (left)
+            screen(2)
+            for (i in 1:length(sub)) if (sub[[i]]$name==click) break
+            y<-sub[[i]]
+         }
+        else cat("this is a tip, you have to choose a node\n")
+
+      }
+    on.exit(return(y))
+}
diff --git a/R/subtrees.R b/R/subtrees.R
new file mode 100644 (file)
index 0000000..bd5bab9
--- /dev/null
@@ -0,0 +1,55 @@
+## subtrees.R (2008-04-14)
+
+##  All subtrees of a Phylogenetic Tree
+
+## Copyright 2008 Damien de Vienne
+
+## This file is part of the R-package `ape'.
+## See the file ../COPYING for licensing issues.
+
+subtrees<-function(tree, wait = FALSE)
+{
+N.tip<-Ntip (tree)
+N.node<-Nnode(tree)
+limit<-N.tip+N.node
+sub<-list(N.node)
+u<-0
+
+  for (k in (N.tip+1):limit)
+  {
+ u<-u+1
+       if (wait==TRUE) cat("wait... Node",u,"out of", N.node, "treated\n")
+  fils<-NULL
+  pere<-res <- k
+       repeat
+       {
+       for (i in 1: length(pere)) fils<-c(fils, tree$edge[,2][tree$edge[,1]==pere[i]])
+       res<-c(res, fils)
+      pere<-fils
+       fils<-NULL
+       if (length(pere)==0) break
+       }
+
+  len<-res[res>N.tip]
+   if (u==1) {
+       tree2<-tree
+       len<-(N.tip+1):limit
+       }
+   else {
+  len.tip<-res[res<N.tip+1]
+  vec<-1:length(tree$tip.label)
+  len.tip.stay<-setdiff(vec, len.tip)
+  tree2<-drop.tip(tree, len.tip.stay)
+         }
+  sub[[u]]<-tree2
+  sub[[u]]$name<-k
+  #sub[[u]]$name<-tree2$node.label[1]
+  sub[[u]]$Ntip<-Ntip(tree2)
+  sub[[u]]$Nnode<-Nnode(tree2)
+  if (is.null(tree$node.label))
+       sub[[u]]$node.label<-len
+
+  }
+return(sub)
+cat("\n")
+}
index 270cf3df1086f2313524cdeedaebdcbdd7e76215..49deac2b013ed74ae6dc17c8b18c6a59277b56fd 100644 (file)
--- a/R/zoom.R
+++ b/R/zoom.R
@@ -1,8 +1,8 @@
-## zoom.R (2004-12-17)
+## zoom.R (2008-04-16)
 
 ##   Zoom on a Portion of a Phylogeny
 
-## Copyright 2003-2004 Emmanuel Paradis
+## Copyright 2003-2008 Emmanuel Paradis
 
 ## This file is part of the R-package `ape'.
 ## See the file ../COPYING for licensing issues.
@@ -13,7 +13,7 @@ zoom <- function(phy, focus, subtree = FALSE, col = rainbow, ...)
     n <- length(focus)
     for (i in 1:n)
       if (is.character(focus[[i]]))
-        focus[[i]] <- which(phy$tip.label == focus[[i]])
+        focus[[i]] <- which(phy$tip.label %in% focus[[i]]) # fix by Yan Wong
     if (is.function(col))
       if (deparse(substitute(col)) == "grey")
         col <- grey(1:n/n) else col <- col(n)
@@ -27,7 +27,7 @@ zoom <- function(phy, focus, subtree = FALSE, col = rainbow, ...)
     M <- matrix(0, nr, nc)
     x <- c(rep(1, nr), 2:(n + 1))
     M[1:length(x)] <- x
-    layout(M, c(1, rep(3 / (nc - 1), nc - 1)))
+    layout(M, c(1, rep(3/(nc - 1), nc - 1)))
     phy$tip.label <- rep("", length(phy$tip.label))
     colo <- rep("black", dim(phy$edge)[1])
     for (i in 1:n)
diff --git a/Thanks b/Thanks
index f28cc14b9c22e164cc57a19878f31d3a04f40112..8b19985a8df76189b0257a7f49c2ddfc73845fdd 100644 (file)
--- a/Thanks
+++ b/Thanks
@@ -1,18 +1,18 @@
 The following persons and institutions helped in the development of
 APE at one stage or another.
 
-  Many users gave important feed-back with their encouragements,
-  comments, or bug reports: thanks to all of you!
+Many users gave important feed-back with their encouragements,
+comments, or bug reports: thanks to all of you!
 
-  Significant bug fixes were provided by James Bullard, Éric Durand,
-  Olivier François, Bret Larget, Klaus Schliep, and Li-San Wang.
-  Contact me if I forgot someone.
+Significant bug fixes were provided by James Bullard, Éric Durand,
+Olivier François, Bret Larget, Klaus Schliep, Li-San Wang, and
+Yan Wong. Contact me if I forgot someone.
 
-  Kurt Hornik, of the R Core Team, helped in several occasions to
-  fix some problems and bugs.
+Kurt Hornik, of the R Core Team, helped in several occasions to
+fix some problems and bugs.
 
-  Financial support was provided in the early development of APE by
-  the French "Programme inter-EPST Bioinformatique" (2001-2003).
+Financial support was provided in the early development of APE by
+the French "Programme inter-EPST Bioinformatique" (2001-2003).
 
-  Financial support was provided by the Department of Information
-  Systems of IRD in form a "SPIRALES" project (2006).
+Financial support was provided by the Department of Information
+Systems of IRD in form a "SPIRALES" project (2006).
diff --git a/man/plot.cophylo.Rd b/man/plot.cophylo.Rd
new file mode 100644 (file)
index 0000000..38ce54a
--- /dev/null
@@ -0,0 +1,53 @@
+\name{plot.cophylo}
+\alias{plot.cophylo}
+\title{Plots two phylogenetic trees face to face with the links between the tips.}
+\description{
+  This function plots two trees face to face with the links if specified. It is possible to rotate the branches of each tree around the nodes by clicking.
+}
+\usage{
+plot.cophylo(phy1, phy2, assoc=NULL, use.edge.length=FALSE,space=0, length.line=1, gap=2, type="phylogram", rotate=FALSE, col="red", show.tip.label=TRUE, font=3)
+}
+
+\arguments{
+  \item{phy1, phy2}{two objects of class \code{"phylo"}.}
+  \item{assoc}{a matrix with 2 columns specifying the associations between the tips. If NULL, no links will be drawn.}
+  \item{use.edge.length}{a logical indicating whether the branch lengths should be used to plot the trees; default is FALSE.}
+  \item{space}{a positive value that specifies the distance between the two trees.}
+  \item{length.line}{a positive value that specifies the length of the horizontal line associated to each taxa. Default is 1.}
+  \item{gap}{a value specifying the distance between the tips of the phylogeny and the lines.}
+  \item{type}{a character string specifying the type of phylogeny to be drawn; it must be one of "phylogram" (the default) or "cladogram".}
+  \item{rotate}{a logical indicating whether the nodes of the phylogeny can be rotated by clicking. Default is FALSE.}
+  \item{col}{a character string indicating the color to be used for the links. Default is red.}
+  \item{show.tip.label}{a logical indicating whether to show the tip labels on the phylogeny (defaults to 'TRUE', i.e. the labels are shown).}
+  \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).}
+}
+\details{
+The aim of this function is to plot simultaneously two phylogenetic trees with associated taxa. The two trees do not necessarily have the same number of tips and more than one tip in one phylogeny can be associated with a tip in the other.
+
+The association matrix used to draw the links has to be a matrix with two columns containing the names of the tips. One line in the matrix represents one link on the plot. The first column of the matrix has to contain tip labels of the first tree (\code{phy1}) and the second column of the matrix, tip labels of the second tree (\code{phy2}). There is no limit (low or high) for the number of lines in the matrix. A matrix with two colums and one line will give a plot with one link.
+
+Arguments \code{gap}, \code{length.line} and \code{space} have to be changed to get a nice plot of the two phylogenies. Note that the function takes into account the length of the character strings corresponding to the names at the tips, so that the lines do not overwrite those names.
+
+The \code{rotate} argument can be used to transform both phylogenies in order to get the more readable plot (typically by decreasing the number of crossing lines). This can be done by clicking on the nodes. The escape button or right click take back to the console.
+}
+\author{Damien de Vienne \email{damien.de-vienne@u-psud.fr}}
+\seealso{
+  \code{\link{plot.phylo}}, \code{\link{rotate}}
+}
+\examples{
+#two random trees
+tree1<-rtree(40) #random tree with 40 leaves
+tree2<-rtree(20) #random tree with 20 leaves
+
+#creation of the association matrix
+association<-matrix(ncol=2, nrow=40)
+association[,1]<-association[,2]<-tree2$tip.label
+
+#plot
+plot.cophylo(tree1, tree2, assoc=association, length.line=4, space=28, gap=3)
+
+#plot with rotations
+plot.cophylo(tree1, tree2, assoc=association, length.line=4, space=28, gap=3, rotate=TRUE)
+
+}
+\keyword{hplot}
diff --git a/man/subtreeplot.Rd b/man/subtreeplot.Rd
new file mode 100644 (file)
index 0000000..c9f80ce
--- /dev/null
@@ -0,0 +1,39 @@
+\name{subtreeplot}
+\alias{subtreeplot}
+\title{Zoom on a Portion of a Phylogeny by Successive Clicks}
+\description{
+  This function plots simultaneously a whole phylogenetic tree
+  (supposedly large) and a portion of it determined by clicking on the nodes of the phylogeny. On exit, returns the last subtree visualized.
+}
+\usage{
+subtreeplot(phy, wait=FALSE, ...)
+}
+
+\arguments{
+  \item{x}{an object of class \code{"phylo"}.}
+  \item{wait}{a logical indicating whether the node beeing processed should be printed (useful for big phylogenies).}
+  \item{...}{further arguments passed to \code{plot.phylo}.}
+}
+\details{
+  This function aims at easily exploring very large trees. The main argument is
+  a phylogenetic tree, and the second one is a logical indicating whether a waiting message should be printed while the calculation is being processed. 
+
+  The whole tree is plotted on the left-hand side in half of the device. The
+  subtree is plotted on the right-hand side in the other half. The user clicks on the nodes in the complete tree and the subtree corresponding to this node is ploted in the right-hand side. There is no limit for the number of clicks that can be done. On exit, the subtree on the right hand side is returned. 
+
+  To use a subtree as the new tree in which to zoom, the user has to use the function many times. This can however be done in a single command line (see example 2).
+}
+\author{Damien de Vienne \email{damien.de-vienne@u-psud.fr}}
+\seealso{
+  \code{\link{plot.phylo}}, \code{\link{drop.tip}}, \code{\link{subtrees}}
+}
+\examples{
+#example 1: simple
+tree1<-rtree(50) #random tree with 50 leaves
+tree2<-subtreeplot(tree1, wait=TRUE) # on exit, tree2 will be a subtree of tree1.
+
+#example 2: more than one zoom
+tree1<-rtree(60)
+tree2<-subtreeplot(subtreeplot(subtreeplot(tree1))) #allows three succssive zooms.
+}
+\keyword{hplot}
diff --git a/man/subtrees.Rd b/man/subtrees.Rd
new file mode 100644 (file)
index 0000000..b59d709
--- /dev/null
@@ -0,0 +1,39 @@
+\name{subtrees}
+\alias{subtrees}
+\title{All subtrees of a Phylogenetic Tree}
+\usage{
+subtrees(x, wait=FALSE)
+}
+\arguments{
+  \item{x}{an object of class \code{"phylo"}.}
+  \item{wait}{a logical indicating whether the node beeing processed should be printed (useful for big phylogenies).}
+}
+\description{
+  This function returns a list of all the subtrees of a phylogenetic tree.
+}
+\author{Damien de Vienne \email{damien.de-vienne@u-psud.fr}}
+\see also{
+  \code{\link{zoom}}, \code{\link{subtreeplot}} for functions extracting particular subtrees.
+}
+\value{
+  \code{subtrees} returns a list of trees of class \code{"phylo"} and returns invisibly for each subtree a list with the following
+  components:
+
+  \item{tip.label}
+  \item{node.label}
+  \item{Ntip}
+  \item{Nnode}
+}
+\examples{
+### Random tree with 12 leaves
+phy<-rtree(12)
+par(mfrow=c(4,3))
+plot(phy, sub="Complete tree")
+
+### Extract the subtrees
+l<-subtrees(phy)
+
+### plot all the subtrees
+for (i in 1:11) plot(l[[i]], sub=paste("Node", l[[i]]$node.label[1]))
+par(mfrow=c(1,1))
+}