o write.nexus() did not translate the taxa names when asked for.
+ o plot.phylo(type = "fan") did not rotate the tip labels correctly
+ when the tree has branch lengths.
+
CHANGES IN APE VERSION 2.4
Package: ape
Version: 2.4-1
-Date: 2009-11-03
+Date: 2009-11-10
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, Daniel Lawson, Vincent Lefort, Pierre Legendre, Jim Lemon, Yvonnick Noel, Johan Nylander, Rainer Opgen-Rhein, Korbinian Strimmer, Damien de Vienne
Maintainer: Emmanuel Paradis <Emmanuel.Paradis@ird.fr>
sh.test <- function(..., x, model = DNAmodel(), B = 100)
.Defunct(msg = '\'sh.test\' has been removed from ape,
see help("ape-defunct") for details.')
-
-heterozygosity <- function (x, variance = FALSE)
- .Defunct(msg = '\'heterozygosity\' has been moved from ape to pegas,
- see help("ape-defunct") for details.')
-
-H <- function(x, variance = FALSE)
- heterozygosity (x, variance = FALSE)
-
-nuc.div <- function(x, variance = FALSE, pairwise.deletion = FALSE)
- .Defunct(msg = '\'nuc.div\' has been moved from ape to pegas,
- see help("ape-defunct") for details.')
-
-theta.h <- function(x, standard.error = FALSE)
- .Defunct(msg = '\'theta.h\' has been moved from ape to pegas,
- see help("ape-defunct") for details.')
-
-theta.k <- function(x, n = NULL, k = NULL)
- .Defunct(msg = '\'theta.k\' has been moved from ape to pegas,
- see help("ape-defunct") for details.')
-
-theta.s <- function(s, n, variance = FALSE)
- .Defunct(msg = '\'theta.s\' has been moved from ape to pegas,
- see help("ape-defunct") for details.')
-## plot.phylo.R (2009-10-27)
+## plot.phylo.R (2009-11-10)
## Plot Phylogenies
}
}
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)
--- /dev/null
+## plotPhyloCoor.R (2008-04-30)
+
+## 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.
+
+plotPhyloCoor <-
+ 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)
+}
--- /dev/null
+(((((Struthionidae:17.1,Rheidae:17.1):0.8,
+(Casuariidae:9.5,Apterygidae:9.5):8.4):3.9,Tinamidae:21.8):4.1,
+(((Cracidae:19.8,Megapodiidae:19.8):1.8,
+((Phasianidae:12.8,Numididae:12.8):2.3,Odontophoridae:15.1):6.5):1.3,
+((Anhimidae:12.4,Anseranatidae:12.4):3.7,
+(Dendrocygnidae:9.8,Anatidae:9.8):6.3):6.8):3.0):2.1,
+(Turnicidae:27.0,(((Indicatoridae:11.0,Picidae:11.0):5.5,
+(Megalaimidae:12.8,(Lybiidae:11.5,Ramphastidae:11.5):1.3):3.7):9.8,
+(((Galbulidae: 17.5,Bucconidae: 17.5):6.9,
+(((Bucerotidae:9.2,Bucorvidae:9.2):11.6,
+(Upupidae:17.0,(Phoeniculidae:10.2,Rhinopomastidae:10.2):6.8):3.8):2.6,
+(Trogonidae:22.1,((Coraciidae:13.9,Leptosomidae:13.9):7.1,
+(Meropidae:19.7,(Momotidae:17.7,(Todidae:16.5,(Alcedinidae:15.5,
+(Dacelonidae:12.0,Cerylidae:12.0):3.5):1.0):1.2):2.0):1.3):1.1):1.3):1.0):0.6,
+(Coliidae:24.5,
+((((Cuculidae:13.0,Centropidae:13.0):1.5,Coccyzidae:14.5):3.1,
+(Opisthocomidae:16.4,(Crotophagidae:14.5,Neomorphidae:14.5):1.9):1.2):6.1,
+(Psittacidae:23.1,
+((((Apodidae:9.5,Hemiprocnidae:9.5):11.8,Trochilidae:21.3):0.6,
+(Musophagidae:20.4,((Tytonidae:13.6,Strigidae:13.6):5.5,
+(Aegothelidae:18.8,((Podargidae:10.3,Batrachostomidae:10.3):7.6,
+((Steatornithidae:15.8,Nyctibiidae:15.8):1.1,
+(Eurostopodidae:12.3,Caprimulgidae:12.3):4.6):1.0):0.9):0.3):1.3):1.5):0.6,
+((Columbidae:20.8,(((Eurypygidae:17.5,
+(Otididae:16.9,(((Gruidae:9.2,Heliornithidae:9.2):3.5,
+Psophiidae:12.7):2.3,Cariamidae:15.0,Rhynochetidae:15.0):1.9):0.6):1.6,Rallidae:19.1):1.0,
+((Pteroclidae:17.1,
+((((Thinocoridae:10.3,Pedionomidae:10.3):3.0,Scolopacidae:13.3):0.8,
+(Rostratulidae:12.5,Jacanidae:12.5):1.6):1.5,
+((Chionididae:11.5,(Burhinidae:10.8,Charadriidae:10.8):0.7):1.3,
+(Glareolidae:8.1,Laridae:8.1):4.7):2.8):1.5):1.6,
+(((Accipitridae:10.4,Sagittariidae:10.4):4.8,Falconidae:15.2):1.2,
+(Podicipedidae:14.9,(Phaethontidae:14.0,
+(((Sulidae:11.0,Anhingidae:11.0):1.1,Phalacrocoracidae:12.1):1.2,
+(Ardeidae:12.4,(Scopidae:11.9,
+(Phoenicopteridae:11.5,(Threskiornithidae:11.1,
+((Pelecanidae:10.1,Ciconiidae:10.1):0.8,
+(Fregatidae:10.7,(Spheniscidae:10.4,(Gaviidae:10.0,
+Procellariidae:10.0):0.4):0.3):0.2):0.2):0.4):0.4):0.5):0.9):0.7):0.9):1.5):2.3):1.4):0.7):0.8,
+((Acanthisittidae:17.9,((Pittidae:12.1,Eurylaimidae:12.1):3.7,
+(Tyrannidae:13.8,(Thamnophilidae:13.5,(Furnariidae:12.1,(Formicariidae:11.4,
+(Conopophagidae:10.7,Rhinocryptidae:10.7):0.7):0.7):1.4):0.3):2.0):2.1):1.8,
+(((Climacteridae:10.4,(Menuridae:9.9,Ptilonorhynchidae:9.9):0.5):1.3,
+((Maluridae:11.2,(Meliphagidae:9.2,Pardalotidae:9.2):2.0):0.2,
+(Eopsaltriidae:10.6,(Irenidae:10.2,(Orthonychidae:10.0,(Pomatostomidae:9.6,
+(Laniidae:9.1,(Vireonidae:8.8,Corvidae:8.8):0.3):0.5):0.4):0.2):0.4):0.8):0.3):1.1,
+((Bombycillidae:10.6,(Cinclidae:9.7,(Muscicapidae:9.1,Sturnidae:9.1):0.6):0.9):1.1,
+(((Sittidae:10.0,Certhiidae:10.0):0.8,
+(Paridae:10.6,(Aegithalidae:10.4,(Hirundinidae:10.1,
+(Regulidae:9.7,(Pycnonotidae:9.5,(Cisticolidae:9.4,
+(Zosteropidae:9.1,Sylviidae:9.1):0.3):0.1):0.2):0.4):0.3):0.2):0.2):0.3,
+(Alaudidae:10.4,(((Nectariniidae:9.6,
+(Melanocharitidae:9.3,Paramythiidae:9.3):0.3):0.2,
+Passeridae:9.8):0.2,Fringillidae:10.0):0.4):0.7):0.6):1.1):6.9):1.9):0.9):0.6):0.6):0.8):0.5):1.3):0.7):1.0);
--- /dev/null
+(((Struthioniformes:21.8,Tinamiformes:21.8):4.1,
+((Craciformes:21.6,Galliformes:21.6):1.3,Anseriformes:22.9):3.0):2.1,
+(Turniciformes:27.0,(Piciformes:26.3,((Galbuliformes:24.4,
+((Bucerotiformes:20.8,Upupiformes:20.8):2.6,
+(Trogoniformes:22.1,Coraciiformes:22.1):1.3):1.0):0.6,
+(Coliiformes:24.5,(Cuculiformes:23.7,(Psittaciformes:23.1,
+(((Apodiformes:21.3,Trochiliformes:21.3):0.6,
+(Musophagiformes:20.4,Strigiformes:20.4):1.5):0.6,
+((Columbiformes:20.8,(Gruiformes:20.1,Ciconiiformes:20.1):0.7):0.8,
+Passeriformes:21.6):0.9):0.6):0.6):0.8):0.5):1.3):0.7):1.0);