]> git.donarmstrong.com Git - ape.git/commitdiff
code clean-up in DNA.R
authorparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Tue, 11 Mar 2008 12:54:40 +0000 (12:54 +0000)
committerparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Tue, 11 Mar 2008 12:54:40 +0000 (12:54 +0000)
fixed ace() with GLS
added some links in the man pages

git-svn-id: https://svn.mpl.ird.fr/ape/dev/ape@21 6e262413-ae40-0410-9e79-b911bd7a66b7

Changes
DESCRIPTION
R/DNA.R
R/ace.R
man/ace.Rd
man/mlphylo.Rd
man/nj.Rd

diff --git a/Changes b/Changes
index 9a33fa8598b4a3f768cf4386488e56a3cef97ae7..aa313f07b306e42b7e1099614677d627a77a8324 100644 (file)
--- a/Changes
+++ b/Changes
@@ -1,3 +1,13 @@
+               CHANGES IN APE VERSION 2.1-3
+
+
+BUG FIXES
+
+    o An error was fixed in the computation of ancestral character
+      states by generalized least squares in ace().
+
+
+
                CHANGES IN APE VERSION 2.1-2
 
 
index e1d5bea49c47ba0316dd97bd8ed82cc20b66fffe..801dc62d173d82ba9820dfe09196568c22999b60 100644 (file)
@@ -1,6 +1,6 @@
 Package: ape
-Version: 2.1-2
-Date: 2008-02-28
+Version: 2.1-3
+Date: 2008-03-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,
@@ -23,4 +23,4 @@ Description: ape provides functions for reading, writing, plotting,
   the Klastorin-Misawa-Tajima approach. Phylogeny estimation can be done
   with the NJ, BIONJ, ME, and ML methods.
 License: GPL (>= 2)
-URL: http://pbil.univ-lyon1.fr/R/ape/
+URL: http://ape.mlp.ird.fr/
diff --git a/R/DNA.R b/R/DNA.R
index c148ac973efeb4d0e75f71c9d33749cadbe23c8c..e8e2260486503f666486be1791a084a5961f3e3e 100644 (file)
--- a/R/DNA.R
+++ b/R/DNA.R
@@ -1,4 +1,4 @@
-## DNA.R (2008-02-08)
+## DNA.R (2008-03-10)
 
 ##   Manipulations and Comparisons of DNA Sequences
 
@@ -209,8 +209,8 @@ base.freq <- function(x)
 {
     if (is.list(x)) x <- unlist(x)
     n <- length(x)
-    BF <- .C("BaseProportion", as.raw(x), as.integer(n),
-             double(4), DUP = FALSE, NAOK = TRUE, PACKAGE = "ape")[[3]]
+    BF <- .C("BaseProportion", x, n, double(4),
+             DUP = FALSE, NAOK = TRUE, PACKAGE = "ape")[[3]]
     names(BF) <- letters[c(1, 3, 7, 20)]
     BF
 }
@@ -226,8 +226,8 @@ seg.sites <- function(x)
     n <- dim(x)
     s <- n[2]
     n <- n[1]
-    ans <- .C("SegSites", x, as.integer(n), as.integer(s),
-              integer(s), DUP = FALSE, NAOK = TRUE, PACKAGE = "ape")
+    ans <- .C("SegSites", x, n, s, integer(s),
+              DUP = FALSE, NAOK = TRUE, PACKAGE = "ape")
     which(as.logical(ans[[4]]))
 }
 
@@ -268,9 +268,8 @@ dist.dna <- function(x, model = "K80", variance = FALSE, gamma = FALSE,
     n <- n[1]
     BF <- if (is.null(base.freq)) base.freq(x) else base.freq
     if (!pairwise.deletion) {
-        keep <- .C("GlobalDeletionDNA", x, as.integer(n),
-                   as.integer(s), as.integer(rep(1, s)),
-                   PACKAGE = "ape")[[4]]
+        keep <- .C("GlobalDeletionDNA", x, n, s,
+                   rep(1L, s), PACKAGE = "ape")[[4]]
         x <- x[,  as.logical(keep)]
         s <- dim(x)[2]
     }
@@ -278,8 +277,7 @@ dist.dna <- function(x, model = "K80", variance = FALSE, gamma = FALSE,
     var <- if (variance) double(Ndist) else 0
     if (!gamma) gamma <- alpha <- 0
     else alpha <- gamma <- 1
-    d <- .C("dist_dna", x, as.integer(n), as.integer(s),
-            as.integer(imod), double(Ndist), BF,
+    d <- .C("dist_dna", x, n, s, imod, double(Ndist), BF,
             as.integer(pairwise.deletion), as.integer(variance),
             var, as.integer(gamma), alpha, DUP = FALSE, NAOK = TRUE,
             PACKAGE = "ape")
diff --git a/R/ace.R b/R/ace.R
index 3e5d16ff5e036614d7a3cf4321f70f9306e17351..a67e6cfbb7e4e05813ba134c7a0293ec46a9e4e9 100644 (file)
--- a/R/ace.R
+++ b/R/ace.R
@@ -1,8 +1,8 @@
-## ace.R (2007-12-14)
+## ace.R (2008-03-10)
 
 ##     Ancestral Character Estimation
 
-## Copyright 2005-2007 Emmanuel Paradis and Ben Bolker
+## Copyright 2005-2008 Emmanuel Paradis and Ben Bolker
 
 ## This file is part of the R-package `ape'.
 ## See the file ../COPYING for licensing issues.
@@ -102,7 +102,10 @@ did not match: the former were ignored in the analysis.')
             V <- corMatrix(Initialize(corStruct, data.frame(x)),
                            corr = FALSE)
             invV <- solve(V)
-            obj$ace <- varAY %*% invV %*% x
+            o <- gls(x ~ 1, correlation = Initialize(corStruct, data.frame(x)))
+            GM <- o$coefficients
+            obj$ace <- drop(varAY %*% invV %*% (x - GM) + GM)
+            names(obj$ace) <- (nb.tip + 1):(nb.tip + nb.node)
             if (CI) {
                 CI95 <- matrix(NA, nb.node, 2)
                 se <- sqrt((varA - varAY %*% invV %*% t(varAY))[cbind(1:nb.node, 1:nb.node)])
index edcab533e32c4a87d6fde5f498318a666cf74787..85cfb210bbbea57af3f7f0786d6b4f4028ea8e89 100644 (file)
@@ -65,9 +65,9 @@ ace(x, phy, type = "continuous", method = "ML", CI = TRUE,
   can be fitted by maximum likelihood (the default, Schluter et
   al. 1997), least squares (\code{method = "pic"}, Felsenstein 1985), or
   generalized least squares (\code{method = "GLS"}, Martins and Hansen
-  1997). In the latter case, the specification of \code{phy} and
-  \code{model} are actually ignored: it is instead given through a
-  correlation structure with the option \code{corStruct}.
+  1997, Cunningham et al. 1998). In the latter case, the specification
+  of \code{phy} and \code{model} are actually ignored: it is instead
+  given through a correlation structure with the option \code{corStruct}.
 
   For discrete characters (\code{type = "discrete"}), only maximum
   likelihood estimation is available (Pagel 1994). The model is
@@ -108,6 +108,11 @@ ace(x, phy, type = "continuous", method = "ML", CI = TRUE,
   \item{call}{the function call.}
 }
 \references{
+  Cunningham, C. W., Omland, K. E. and Oakley, T. H. (1998)
+  Reconstructing ancestral character states: a critical
+  reappraisal. \emph{Trends in Ecology & Evolution}, \bold{13},
+  361--366.
+
   Felsenstein, J. (1985) Phylogenies and the comparative
   method. \emph{American Naturalist}, \bold{125}, 1--15.
 
index 7915604567f0f7225487c55550984d46b4c1195f..03effb58f8193df2dc5473c3c3977f21c299012b 100644 (file)
@@ -97,6 +97,6 @@ mlphylo(x, phy, model = DNAmodel(), search.tree = FALSE,
 \author{Emmanuel Paradis \email{Emmanuel.Paradis@mpl.ird.fr}}
 \seealso{
   \code{\link{DNAmodel}}, \code{\link{nj}}, \code{\link{read.dna}},
-  \code{\link{summary.phylo}}
+  \code{\link{summary.phylo}}, \code{\link{bionj}}, \code{\link{fastme}}
 }
 \keyword{models}
index 9fd2adb66aebbac5e3018e79a6d88b7a9d798456..3b8cb64c531f690db46b2d308f0062a6f96d8353 100644 (file)
--- a/man/nj.Rd
+++ b/man/nj.Rd
@@ -22,7 +22,8 @@ nj(X)
 \author{Emmanuel Paradis \email{Emmanuel.Paradis@mpl.ird.fr}}
 \seealso{
   \code{\link{write.tree}}, \code{\link{read.tree}},
-  \code{\link{dist.dna}}, \code{\link{mlphylo}}
+  \code{\link{dist.dna}}, \code{\link{mlphylo}}, \code{\link{bionj}},
+  \code{\link{fastme}}
 }
 \examples{
 ### From Saitou and Nei (1987, Table 1):