]> git.donarmstrong.com Git - ape.git/blobdiff - R/DNA.R
a collection of bug fixes
[ape.git] / R / DNA.R
diff --git a/R/DNA.R b/R/DNA.R
index 7599265ea7ba08f3792cfd3fc5034b0b75889b61..dd9c60bb63ace9abfe1350c73664e365ed91ac36 100644 (file)
--- a/R/DNA.R
+++ b/R/DNA.R
@@ -1,4 +1,4 @@
-## DNA.R (2009-05-10)
+## DNA.R (2009-09-06)
 
 ##   Manipulations and Comparisons of DNA Sequences
 
@@ -19,6 +19,7 @@ del.gaps <- function(x)
         n <- dim(x)[1]
         y <- vector("list", n)
         for (i in 1:n) y[[i]] <- x[i, ]
+        names(y) <- rownames(x)
         x <- y
         rm(y)
     }
@@ -142,6 +143,9 @@ cbind.DNAbin <-
     ans
 }
 
+c.DNAbin <- function(..., recursive = FALSE)
+    structure(NextMethod("c"), class = "DNAbin")
+
 print.DNAbin <- function(x, ...)
 {
     n <- 1 # <- if is.vector(x)
@@ -270,9 +274,13 @@ GC.content <- function(x) sum(base.freq(x)[2:3])
 seg.sites <- function(x)
 {
     if (is.list(x)) x <- as.matrix(x)
-    n <- dim(x)
-    s <- n[2]
-    n <- n[1]
+    if (is.vector(x)) n <- 1
+    else { # 'x' is a matrix
+        n <- dim(x)
+        s <- n[2]
+        n <- n[1]
+    }
+    if (n == 1) return(integer(0))
     ans <- .C("SegSites", x, n, s, integer(s),
               DUP = FALSE, NAOK = TRUE, PACKAGE = "ape")
     which(as.logical(ans[[4]]))