]> git.donarmstrong.com Git - ape.git/blobdiff - R/read.dna.R
final commit for ape 3.0-8
[ape.git] / R / read.dna.R
index 9e46cba67bbc81b5eed7624232e5c8185519e5c2..ab8051e023afeb2c48c4613348fe360c4dce224c 100644 (file)
@@ -1,8 +1,8 @@
-## read.dna.R (2012-12-27)
+## read.dna.R (2013-04-02)
 
 ##   Read DNA Sequences in a File
 
-## Copyright 2003-2012 Emmanuel Paradis
+## Copyright 2003-2013 Emmanuel Paradis
 
 ## This file is part of the R-package `ape'.
 ## See the file ../COPYING for licensing issues.
@@ -11,11 +11,10 @@ read.FASTA <- function(file)
 {
     sz <- file.info(file)$size
     x <- readBin(file, "raw", sz)
-    if (Sys.info()[1] == "Windows") {
-        icr <- which(x == as.raw(0x0d)) # CR
-        x <- x[-icr]
-    }
+    icr <- which(x == as.raw(0x0d)) # CR
+    if (length(icr)) x <- x[-icr]
     res <- .Call("rawStreamToDNAbin", x, PACKAGE = "ape")
+    names(res) <- sub("^ +", "", names(res)) # to permit phylosim
     class(res) <- "DNAbin"
     res
 }
@@ -47,7 +46,6 @@ read.dna <- function(file, format = "interleaved", skip = 0,
     } else {
         X <- scan(file = file, what = "", sep = "\n", quiet = TRUE,
                   skip = skip, nlines = nlines, comment.char = comment.char)
-
         if (format %in% formats[1:2]) {
             ## need to remove the possible leading spaces and/or tabs in the first line
             fl <- gsub("^[[:blank:]]+", "", X[1])
@@ -106,9 +104,10 @@ read.dna <- function(file, format = "interleaved", skip = 0,
                    for (i in 2:n)
                        obj[i, ] <- getNucleotide(X[seq(i, nl, n + 1)])
                })
-
+    }
     if (format != "fasta") {
         rownames(obj) <- taxa
+        if (!as.character) obj <- as.DNAbin(obj)
     } else {
         LENGTHS <- unique(unlist(lapply(obj, length)))
         allSameLength <- length(LENGTHS) == 1
@@ -119,10 +118,15 @@ read.dna <- function(file, format = "interleaved", skip = 0,
             as.matrix <- allSameLength
         }
         if (as.matrix) {
-            obj <- matrix(unlist(obj), ncol = LENGTHS, byrow = TRUE)
+            taxa <- names(obj)
+            n <- length(obj)
+            y <- matrix(as.raw(0), n, LENGTHS)
+            for (i in seq_len(n)) y[i, ] <- obj[[i]]
+            obj <- y
             rownames(obj) <- taxa
+            class(obj) <- "DNAbin"
         }
+        if (as.character) obj <- as.character(obj)
     }
-    if (!as.character) obj <- as.DNAbin(obj)
     obj
 }