X-Git-Url: https://git.donarmstrong.com/?a=blobdiff_plain;f=R%2FDNA.R;h=e8e2260486503f666486be1791a084a5961f3e3e;hb=a3ddfc06dd47c560b3ec5869ac104b0c68441eb1;hp=b5f472be1ed6f53115220335dee71e00747f2052;hpb=6dfbab243973c0c3fa2e6d02b190aefbe5a67280;p=ape.git diff --git a/R/DNA.R b/R/DNA.R index b5f472b..e8e2260 100644 --- a/R/DNA.R +++ b/R/DNA.R @@ -1,4 +1,4 @@ -## DNA.R (2008-01-19) +## 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), 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), PACKAGE = "ape") + ans <- .C("SegSites", x, n, s, integer(s), + DUP = FALSE, NAOK = TRUE, PACKAGE = "ape") which(as.logical(ans[[4]])) } @@ -240,7 +240,7 @@ nuc.div <- function(x, variance = FALSE, pairwise.deletion = FALSE) 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 @@ -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,10 +277,10 @@ 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, PACKAGE = "ape") + var, as.integer(gamma), alpha, DUP = FALSE, NAOK = TRUE, + PACKAGE = "ape") if (variance) var <- d[[9]] d <- d[[5]] if (imod == 11) {