]> git.donarmstrong.com Git - ape.git/blob - R/read.tree.R
final fix in read.nexus() for ape 2.2-1
[ape.git] / R / read.tree.R
1 ## read.tree.R (2008-02-18)
2
3 ##   Read Tree Files in Parenthetic Format
4
5 ## Copyright 2002-2008 Emmanuel Paradis
6
7 ## This file is part of the R-package `ape'.
8 ## See the file ../COPYING for licensing issues.
9
10 tree.build <- function(tp)
11 {
12     add.internal <- function() {
13         edge[j, 1] <<- current.node
14         edge[j, 2] <<- current.node <<- node <<- node + 1L
15         j <<- j + 1L
16     }
17     add.terminal <- function() {
18         edge[j, 1] <<- current.node
19         edge[j, 2] <<- tip
20         X <- unlist(strsplit(tpc[k], ":"))
21         tip.label[tip] <<- X[1]
22         edge.length[j] <<- as.numeric(X[2])
23         k <<- k + 1L
24         tip <<- tip + 1L
25         j <<- j + 1L
26     }
27     go.down <- function() {
28         l <- which(edge[, 2] == current.node)
29         X <- unlist(strsplit(tpc[k], ":"))
30         node.label[current.node - nb.tip] <<- X[1]
31         edge.length[l] <<- as.numeric(X[2])
32         k <<- k + 1L
33         current.node <<- edge[l, 1]
34     }
35     if (!length(grep(",", tp))) {
36         obj <- list(edge = matrix(c(2L, 1L), 1, 2))
37         tp <- unlist(strsplit(tp, "[\\(\\):;]"))
38         obj$edge.length <- as.numeric(tp[3])
39         obj$Nnode <- 1L
40         obj$tip.label <- tp[2]
41         if (length(tp) == 4) obj$node.label <- tp[4]
42         class(obj) <- "phylo"
43         return(obj)
44     }
45
46     tpc <- unlist(strsplit(tp, "[\\(\\),;]"))
47     tpc <- tpc[nzchar(tpc)]
48     ## the following 2 lines are (slightly) faster than using gsub()
49     tsp <- unlist(strsplit(tp, NULL))
50     skeleton <- tsp[tsp %in% c("(", ")", ",", ";")]
51     nsk <- length(skeleton)
52     nb.node <- sum(skeleton == ")")
53     nb.tip <- sum(skeleton == ",") + 1
54     ## We will assume there is an edge at the root;
55     ## if so, it will be removed and put into a vector
56     nb.edge <- nb.node + nb.tip
57     node.label <- character(nb.node)
58     tip.label <- character(nb.tip)
59
60     edge.length <- numeric(nb.edge)
61     edge <- matrix(0L, nb.edge, 2)
62     current.node <- node <- as.integer(nb.tip + 1) # node number
63     edge[nb.edge, 2] <- node #
64
65     ## j: index of the line number of edge
66     ## k: index of the line number of tpc
67     ## tip: tip number
68     j <- k <- tip <- 1L
69
70     for (i in 2:nsk) {
71         if (skeleton[i] == "(") add.internal() # add an internal branch (on top)
72         if (skeleton[i] == ",") {
73             if (skeleton[i - 1] != ")") add.terminal() # add a terminal branch
74         }
75         if (skeleton[i] == ")") {
76             if (skeleton[i - 1] == ",") { # add a terminal branch and go down one level
77                 add.terminal()
78                 go.down()
79             }
80             if (skeleton[i - 1] == ")") go.down() # go down one level
81         }
82     }
83
84     edge <- edge[-nb.edge, ]
85     obj <- list(edge = edge, Nnode = nb.node, tip.label = tip.label)
86     root.edge <- edge.length[nb.edge]
87     edge.length <- edge.length[-nb.edge]
88     if (!all(is.na(edge.length))) # added 2005-08-18
89         obj$edge.length <- edge.length
90     if (is.na(node.label[1])) node.label[1] <- ""
91     if (any(nzchar(node.label))) obj$node.label <- node.label
92     if (!is.na(root.edge)) obj$root.edge <- root.edge
93     class(obj) <- "phylo"
94     obj
95 }
96
97 read.tree <- function(file = "", text = NULL, tree.names = NULL,
98                       skip = 0, comment.char = "#", ...)
99 {
100     if (!is.null(text)) {
101         if (!is.character(text))
102           stop("argument `text' must be of mode character")
103         tree <- text
104     } else {
105         tree <- scan(file = file, what = "", sep = "\n", quiet = TRUE,
106                      skip = skip, comment.char = comment.char, ...)
107     }
108     ## Suggestion from Eric Durand and Nicolas Bortolussi (added 2005-08-17):
109     if (identical(tree, character(0))) {
110         warning("empty character string.")
111         return(NULL)
112     }
113     tree <- gsub("[ \t]", "", tree)
114     tree <- unlist(strsplit(tree, NULL))
115     y <- which(tree == ";")
116     Ntree <- length(y)
117     x <- c(1, y[-Ntree] + 1)
118     ## Suggestion from Olivier François (added 2006-07-15):
119     if (is.na(y[1])) return(NULL)
120     STRING <- character(Ntree)
121     for (i in 1:Ntree)
122         STRING[i] <- paste(tree[x[i]:y[i]], sep = "", collapse = "")
123     colon <- grep(":", STRING)
124     if (!length(colon)) {
125         obj <- lapply(STRING, clado.build)
126     } else if (length(colon) == Ntree) {
127         obj <- lapply(STRING, tree.build)
128     } else {
129         obj <- vector("list", Ntree)
130         obj[colon] <- lapply(STRING[colon], tree.build)
131         nocolon <- (1:Ntree)[!1:Ntree %in% colon]
132         obj[nocolon] <- lapply(STRING[nocolon], clado.build)
133     }
134     for (i in 1:Ntree) {
135         ## Check here that the root edge is not incorrectly represented
136         ## in the object of class "phylo" by simply checking that there
137         ## is a bifurcation at the root
138         ROOT <- length(obj[[i]]$tip.label) + 1
139         if(sum(obj[[i]]$edge[, 1] == ROOT) == 1 && dim(obj[[i]]$edge)[1] > 1)
140             stop(paste("There is apparently two root edges in your file: cannot read tree file.\n  Reading Newick file aborted at tree no.", i, sep = ""))
141     }
142     if (Ntree == 1) obj <- obj[[1]] else {
143         if (!is.null(tree.names)) names(obj) <- tree.names
144         class(obj) <- "multiPhylo"
145     }
146     obj
147 }