]> git.donarmstrong.com Git - ape.git/blobdiff - R/DNA.R
fixing a few bugs...
[ape.git] / R / DNA.R
diff --git a/R/DNA.R b/R/DNA.R
index bd5f1954492527573a7aee1780898aef9584904b..c148ac973efeb4d0e75f71c9d33749cadbe23c8c 100644 (file)
--- a/R/DNA.R
+++ b/R/DNA.R
@@ -1,8 +1,8 @@
-## DNA.R (2007-12-21)
+## DNA.R (2008-02-08)
 
 ##   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.
@@ -210,7 +210,7 @@ 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), PACKAGE = "ape")[[3]]
+             double(4), DUP = FALSE, NAOK = TRUE, PACKAGE = "ape")[[3]]
     names(BF) <- letters[c(1, 3, 7, 20)]
     BF
 }
@@ -227,7 +227,7 @@ seg.sites <- function(x)
     s <- n[2]
     n <- n[1]
     ans <- .C("SegSites", x, as.integer(n), as.integer(s),
-              integer(s), PACKAGE = "ape")
+              integer(s), DUP = FALSE, NAOK = TRUE, PACKAGE = "ape")
     which(as.logical(ans[[4]]))
 }
 
@@ -235,26 +235,12 @@ 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))
+        var <- (n + 1)*ans/(3*(n + 1)*dim(x)[2]) + 2*(n^2 + n + 3)*ans/(9*n*(n - 1))
         ans <- c(ans, var)
     }
     ans
@@ -295,7 +281,8 @@ dist.dna <- function(x, model = "K80", variance = FALSE, gamma = FALSE,
     d <- .C("dist_dna", x, as.integer(n), as.integer(s),
             as.integer(imod), double(Ndist), BF,
             as.integer(pairwise.deletion), as.integer(variance),
-            var, as.integer(gamma), alpha, PACKAGE = "ape")
+            var, as.integer(gamma), alpha, DUP = FALSE, NAOK = TRUE,
+            PACKAGE = "ape")
     if (variance) var <- d[[9]]
     d <- d[[5]]
     if (imod == 11) {