]> git.donarmstrong.com Git - ape.git/commitdiff
fix a bug in nuc.div()
authorparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Mon, 21 Jan 2008 13:58:58 +0000 (13:58 +0000)
committerparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Mon, 21 Jan 2008 13:58:58 +0000 (13:58 +0000)
git-svn-id: https://svn.mpl.ird.fr/ape/dev/ape@15 6e262413-ae40-0410-9e79-b911bd7a66b7

Changes
R/DNA.R
src/dist_dna.c

diff --git a/Changes b/Changes
index af1c2187083ded70f820c256c771674fcc0b6eba..58e0ddbd99fee2c39750d7e59e7923d6369b7fd9 100644 (file)
--- a/Changes
+++ b/Changes
@@ -9,6 +9,12 @@ NEW FEATURES
       (thanks to Vladimir Minin for the code).
 
 
+BUG FIXES
+
+    o nuc.div() returned an incorrect value with the default
+      pairwise.deletion = FALSE.
+
+
 OTHER CHANGES
 
     o The internal codes of bionj(), fastme.bal(), and fastme.ols()
diff --git a/R/DNA.R b/R/DNA.R
index bd5f1954492527573a7aee1780898aef9584904b..b5f472be1ed6f53115220335dee71e00747f2052 100644 (file)
--- a/R/DNA.R
+++ b/R/DNA.R
@@ -1,8 +1,8 @@
-## DNA.R (2007-12-21)
+## DNA.R (2008-01-19)
 
 ##   Manipulations and Comparisons of DNA Sequences
 
-## 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.
@@ -235,24 +235,10 @@ nuc.div <- function(x, variance = FALSE, pairwise.deletion = FALSE)
 {
     if (pairwise.deletion && variance)
       warning("cannot compute the variance of nucleotidic diversity\nwith pairwise deletion: try 'pairwise.deletion = FALSE' instead.")
-
-    n <- dim(x)
-    s <- n[2]
-    n <- n[1]
-
-    ## <FIXME> this should be safely deleted
-    if (!pairwise.deletion) {
-        keep <- .C("GlobalDeletionDNA", x, as.integer(n),
-                   as.integer(s), as.integer(rep(1, s)),
-                   PACKAGE = "ape")[[4]]
-        x <- x[,  as.logical(keep)]
-        s <- dim(x)[2]
-    }
-    ## </FIXME>
-
-    ans <- .C("NucleotideDiversity", x, as.integer(n), as.integer(s),
-              as.integer(pairwise.deletion), double(1), PACKAGE = "ape")[[5]]
-
+    if (is.list(x)) x <- as.matrix(x)
+    n <- dim(x)[1]
+    ans <- sum(dist.dna(x, "raw", pairwise.deletion = pairwise.deletion))/
+        (n*(n - 1)/2)
     if (variance) {
         var <- (n + 1)*ans/(3*(n + 1)*s) + 2*(n^2 + n + 3)*ans/(9*n*(n - 1))
         ans <- c(ans, var)
index 4e02393334a11ccd8d749294e19cff9d6a41f9f1..f10bc4debeacd4b8acf7d80da75af5913b3d0b63 100644 (file)
@@ -1,6 +1,6 @@
-/* dist_dna.c       2007-12-01 */
+/* dist_dna.c       2008-01-19 */
 
-/* Copyright 2005-2007 Emmanuel Paradis
+/* Copyright 2005-2008 Emmanuel Paradis
 
 /* This file is part of the R-package `ape'. */
 /* See the file ../COPYING for licensing issues. */
@@ -988,27 +988,6 @@ void SegSites(unsigned char *x, int *n, int *s, int *seg)
     }
 }
 
-void NucleotideDiversity(unsigned char *x, int *n, int *s,
-                        int *pairdel, double *ans)
-{
-    int i1, i2, s1, s2, Nd, L;
-
-    if (!*pairdel) L = *s;
-
-    for (i1 = 1; i1 < *n; i1++) {
-        for (i2 = i1 + 1; i2 <= *n; i2++) {
-           Nd = 0;
-           if (*pairdel) L = 0;
-           for (s1 = i1 - 1, s2 = i2 - 1; s1 < i1 + *n*(*s - 1); s1+= *n, s2 += *n) {
-                CHECK_PAIRWISE_DELETION
-               if (DifferentBase(x[s1], x[s2])) Nd++;
-           }
-           *ans += ((double) Nd/L);
-       }
-    }
-    *ans /= (*n * (*n - 1)/2);
-}
-
 void GlobalDeletionDNA(unsigned char *x, int *n, int *s, int *keep)
 {
     int i, j;