[Phylobase-commits] r430 - in pkg: R inst/doc man tests

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Wed Apr 22 17:42:53 CEST 2009


Author: francois
Date: 2009-04-22 17:42:53 +0200 (Wed, 22 Apr 2009)
New Revision: 430

Modified:
   pkg/R/class-phylo4.R
   pkg/R/methods-phylo4.R
   pkg/R/setAs-Methods.R
   pkg/inst/doc/phylobase.Rnw
   pkg/man/as-methods.Rd
   pkg/man/hasSingles.Rd
   pkg/man/multiPhylo-class.Rd
   pkg/man/pdata-class.Rd
   pkg/man/phylo4-class.Rd
   pkg/man/phylo4d.Rd
   pkg/man/phylomat-class.Rd
   pkg/man/subset-methods.Rd
   pkg/tests/misctests.R
Log:
Check that the values provided for node labels are not numerical (temporary), and updated
	documentation and vignette accordingly.

Fix bug #417 and improve coercion of multiPhylo - multiPhylo4 - multiPhylo4d

Fix bug in case of printing trees with no edge lengths

Edges are now internally named only they exist

Worked around ape bug in read.tree by creating tree.owls objects rather than calling
	example(read.tree) (bug #416)


Modified: pkg/R/class-phylo4.R
===================================================================
--- pkg/R/class-phylo4.R	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/R/class-phylo4.R	2009-04-22 15:42:53 UTC (rev 430)
@@ -39,16 +39,19 @@
         if(!is.numeric(edge.length)) stop("edge.length is not numeric")
         edge.length <- edge.length
     } else {
-        edge.length <- as.numeric(NULL)
+        edge.length <- numeric(0)
     }
-    if(length(edge.length) != nrow(edge))
-        stop("The number of edge length is different from the number of edges.")
-    ## FM - 2009-04-19
-    ## edge.length is named according to the nodes the edge links together
-    ## (ancestor-descendant). This should allow more robust edge/edge.length
-    ## association and limit the problems associated with reordering trees.
-    names(edge.length) <- paste(edge[,1], edge[,2], sep="-")
 
+    if(length(edge.length) > 0) {
+        if(length(edge.length) != nrow(edge))
+            stop("The number of edge lengths is different from the number of edges.")
+        ## FM - 2009-04-19
+        ## edge.length is named according to the nodes the edge links together
+        ## (ancestor-descendant). This should allow more robust edge/edge.length
+        ## association and limit the problems associated with reordering trees.
+        names(edge.length) <- paste(edge[,1], edge[,2], sep="-")
+    }
+
     ## tip.label
     ntips <- sum(tabulate(na.omit(edge[, 1])) == 0)
     if(is.null(tip.label)) {
@@ -104,7 +107,7 @@
         node.data <- data.frame(labelValues=as.numeric(node.data))
         res at node.label <- node.label
 
-        res <- phylo4d(res, node.data=node.data, use.node.names=F)
+        res <- phylo4d(res, node.data=node.data, use.node.names=FALSE)
         if(is.character(checkval <- checkPhylo4(res))) stop(checkval)
 
         return(res)

Modified: pkg/R/methods-phylo4.R
===================================================================
--- pkg/R/methods-phylo4.R	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/R/methods-phylo4.R	2009-04-22 15:42:53 UTC (rev 430)
@@ -151,6 +151,11 @@
 setReplaceMethod("labels",
                  signature(object="phylo4", value="character"),
    function(object, which = c("tip", "internal", "allnode"), ..., value) {
+
+       tLbl <- as.numeric(value)
+       if(length(grep("[a-zA-Z]", value)) == 0)
+           stop("Labels need to contain characters")
+
        which <- match.arg(which)
        tipOrder <- order(nodeId(object, "tip"))
        intOrder <- order(nodeId(object, "internal"))

Modified: pkg/R/setAs-Methods.R
===================================================================
--- pkg/R/setAs-Methods.R	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/R/setAs-Methods.R	2009-04-22 15:42:53 UTC (rev 430)
@@ -7,7 +7,7 @@
         tip.idx <- 1:nTips(from)
         int.idx <- (nTips(from)+1):dim(from$edge)[1]
         root.node <- as.numeric(setdiff(unique(from$edge[,1]), unique(from$edge[,2])))
-        #from$edge <- rbind(from$edge,c(NA,root.edge))
+
         from$edge <- rbind(from$edge[tip.idx,],c(NA,root.node),from$edge[int.idx,])
         if (!is.null(from$edge.length)) {
             if (is.null(from$root.edge)) {
@@ -22,8 +22,8 @@
         }
     }
     newobj <- phylo4(from$edge, from$edge.length, from$tip.label,
-        node.label = from$node.label, edge.label = from$edge.label)
-    attribs = attributes(from)
+                     node.label = from$node.label, edge.label = from$edge.label)
+    attribs <- attributes(from)
     attribs$names <- NULL
     knownattr <- c("logLik", "order", "origin", "para", "xi")
     known <- names(attribs)[names(attribs) %in% knownattr]
@@ -39,13 +39,14 @@
     phylo4d(as(from, "phylo4"), tip.data = data.frame())
 })
 
+
 setAs("multiPhylo", "multiPhylo4", function(from, to) {
-    y <- lapply(as, from at phylolist, to = "phylo")
-    names(y) <- from at tree.names
-    if (nrow(from at tip.data) > 0)
-        warning("discarded tip data")
-    class(y) <- "multiPhylo"
-    y
+    trNm <- names(from)
+    if(is.null(trNm)) trNm <- character(0)
+    newobj <- new("multiPhylo4", phylolist = lapply(from, function(x)
+                                 as(x, "phylo4")),
+                  tree.names = trNm)
+    newobj
 })
 
 #######################################################
@@ -109,15 +110,14 @@
 ##})
 
 setAs("multiPhylo4", "multiPhylo", function(from, to) {
-    newobj <- new("multiPhylo4", phylolist = lapply(from,
-        as, to = "phylo4"))
+    y <- lapply(from at phylolist, function(x) as(x, "phylo"))
+    names(y) <- from at tree.names
+    if (nrow(from at tip.data) > 0)
+        warning("discarded tip data")
+    class(y) <- "multiPhylo"
+    y
 })
 
-setAs("multiPhylo4d", "multiPhylo", function(from, to) {
-    newobj <- new("multiPhylo4d", phylolist = lapply(from,
-        as, to = "phylo4"), tree.names = names(from), tip.data = data.frame())
-})
-
 #######################################################
 ## Exporting to ade4
 setAs("phylo4", "phylog", function(from, to) {
@@ -152,7 +152,7 @@
         edge.length <- edgeLength(x)[match(nmE, names(x at edge.length))]
     }
     else {
-        edge.length <- rep(NA, nNodes(x))
+        edge.length <- rep(NA, nEdges(x))
     }
 
     label <- labels(x,which="all")[node]

Modified: pkg/inst/doc/phylobase.Rnw
===================================================================
--- pkg/inst/doc/phylobase.Rnw	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/inst/doc/phylobase.Rnw	2009-04-22 15:42:53 UTC (rev 430)
@@ -110,7 +110,7 @@
 A simple way to assign the node numbers as labels (useful for various checks) is
 
 <<>>=
-nodeLabels(g1) <- as.character(sort(nodeId(g1)))
+nodeLabels(g1) <- paste("N", nodeId(g1), sep="")
 head(g1, 5)
 @
 
@@ -305,7 +305,7 @@
 <<keep.source=TRUE>>=
 ## add node labels so we can match to data
 nodeLabels(tree) <- as.character(sort(nodeId(tree)))
-## ordering will make sure that we have ancestor value 
+## ordering will make sure that we have ancestor value
 ## defined before descendant
 tree <- reorder(tree, "preorder")
 edgemat <- edges(tree)
@@ -324,7 +324,7 @@
   }
 nodevals <- data.frame(nodevals)
 treed2 <- phylo4d(tree, all.data=nodevals)
-@ 
+@
 
 
 % ========================================

Modified: pkg/man/as-methods.Rd
===================================================================
--- pkg/man/as-methods.Rd	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/man/as-methods.Rd	2009-04-22 15:42:53 UTC (rev 430)
@@ -42,7 +42,7 @@
 }
 \description{
   Translation functions to convert between phylobase trees or trees+data objects (\code{phylo4}, \code{phylo4d}), and objects used by other comparative methods packages in R:  \code{ape} objects
-  (\code{phylo}, \code{multiPhylo}) \code{ade4} objects (\code{phylog}), and to \code{data.frame} respresentation. 
+  (\code{phylo}, \code{multiPhylo}) \code{ade4} objects (\code{phylog}), and to \code{data.frame} respresentation.
 }
 \section{Methods}{
   \item{coerce}{from one object class to another using \code{as(object,"Class")}, where the \code{object} is of the old class and the returned object is of the new class \code{"Class"}. The \code{as} function examines the class of \code{object} and the new \code{"Class"} specified to choose the proper conversion without additional information from the user. Conversions exist for combinations:
@@ -82,14 +82,14 @@
 
 \author{Ben Bolker, Thibaut Jombart \email{jombart at biomserv.univ-lyon1.fr}, Marguerite Butler, Steve Kembel}
 \seealso{ generic \code{\link[methods]{as}}, \code{\link{phylo4}}, \code{\link{phylo4d}}, \code{\link{extractTree}}, the original \code{\link[ade4]{phylog}} from the
-  \code{ade4} package and \code{\link[ape]{as.phylo}} from the \code{ape} package. 
+  \code{ade4} package and \code{\link[ape]{as.phylo}} from the \code{ape} package.
 }
 \examples{
-library(ape)
-example(read.tree)
-## round trip conversion 
-tree_in_phylo <- tree.owls                # tree is a phylo object 
-(tree_in_phylo4 <- as(tree.owls,"phylo4"))  # phylo converted to phylo4 
+
+tree.owls <- read.tree(text="(((Strix_aluco:4.2,Asio_otus:4.2):3.1,Athene_noctua:7.3):6.3,Tyto_alba:13.5);")
+## round trip conversion
+tree_in_phylo <- tree.owls                # tree is a phylo object
+(tree_in_phylo4 <- as(tree.owls,"phylo4"))  # phylo converted to phylo4
 identical(tree_in_phylo,as(tree_in_phylo4,"phylo"))
 ## test if phylo, and phlyo4 converted to phylo are identical
 ## (no, because of dimnames)

Modified: pkg/man/hasSingles.Rd
===================================================================
--- pkg/man/hasSingles.Rd	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/man/hasSingles.Rd	2009-04-22 15:42:53 UTC (rev 430)
@@ -35,8 +35,8 @@
 }
 \examples{
 library(ape)
-example(read.tree)
-owls4 = as(tree.owls.bis, "phylo4")
+tree.owls.bis <- read.tree(text = "((Strix_aluco:4.2,Asio_otus:4.2):3.1,Athene_noctua:7.3);")
+owls4 <- as(tree.owls.bis, "phylo4")
 hasPoly(owls4)
 hasSingle(owls4)
 }

Modified: pkg/man/multiPhylo-class.Rd
===================================================================
--- pkg/man/multiPhylo-class.Rd	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/man/multiPhylo-class.Rd	2009-04-22 15:42:53 UTC (rev 430)
@@ -57,12 +57,10 @@
   }
   \author{Ben Bolker, Thibaut Jombart}   
 \examples{
-  library(ape)
-  example(read.tree)
-  p1 = tree.owls
-  P1 = as(tree.owls, "phylo4")
-  P1
-  sumryP1 = summary(P1)
-  sumryP1
+### An extract from Sibley and Ahlquist (1990)
+cat("(((Strix_aluco:4.2,Asio_otus:4.2):3.1,Athene_noctua:7.3):6.3,Tyto_alba:13.5);", file = "ex.tre", sep = "\n")
+tree.owls <- read.tree("ex.tre", keep.multi = TRUE)
+tree.owls
+(as(tree.owls, "multiPhylo4"))
 }
 \keyword{classes}

Modified: pkg/man/pdata-class.Rd
===================================================================
--- pkg/man/pdata-class.Rd	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/man/pdata-class.Rd	2009-04-22 15:42:53 UTC (rev 430)
@@ -18,13 +18,13 @@
   Objects can be created by calls of the form \code{new("pdata", ...)}.
 }
 \section{Slots}{
-	 \describe{
-	   \item{\code{data}:}{A data frame of tip or node data.  Can be
-	     accessed transparently with any of the data frame accessor methods}
-	   \item{\code{type}:}{A factor with length equal to \code{ncol(data)}
-	     and levels ("multitype","binary","continuous","DNA","RNA","aacid")}
-	   \item{\code{comment}:}{A character vector of length \code{ncol(data)}}
-	   \item{\code{metadata}:}{An arbitrary list, for storing other user-defined metadata}
+         \describe{
+           \item{\code{data}:}{A data frame of tip or node data.  Can be
+             accessed transparently with any of the data frame accessor methods}
+           \item{\code{type}:}{A factor with length equal to \code{ncol(data)}
+             and levels ("multitype","binary","continuous","DNA","RNA","aacid")}
+           \item{\code{comment}:}{A character vector of length \code{ncol(data)}}
+           \item{\code{metadata}:}{An arbitrary list, for storing other user-defined metadata}
 }
 }
 \section{Methods}{
@@ -35,8 +35,11 @@
     \item{\[\$<-}{\code{signature(x = "pdata")}: set data rows, columns or elements}
     \item{\[\[<-}{\code{signature(x = "pdata")}: set data columns or elements}
     \item{\[\[}{\code{signature(x = "pdata", i = "ANY", j = "ANY")}: access data columns or elements }
-    \item{\[\[}{\code{signature(x = "pdata", i = "ANY", j = "missing")}: set data columns or elements }}
-  \author{Ben Bolker}
+    \item{\[\[}{\code{signature(x = "pdata", i = "ANY", j = "missing")}: set data columns
+    or elements }
+    }
+
+\author{Ben Bolker}
   % commented to eliminate Note: on build
   %\examples{
 %}

Modified: pkg/man/phylo4-class.Rd
===================================================================
--- pkg/man/phylo4-class.Rd	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/man/phylo4-class.Rd	2009-04-22 15:42:53 UTC (rev 430)
@@ -72,30 +72,29 @@
   }
 \seealso{the \code{\link{phylo4}} constructor, the \code{\link{checkPhylo4}}
   function to check the validity of \code{phylo4} objects. See also the \code{\link{phylo4d}} constructor and the \linkS4class{phylo4d} class.}
-\author{Ben Bolker, Thibaut Jombart}   
+\author{Ben Bolker, Thibaut Jombart}
 \examples{
-  library(ape)
-  example(read.tree)
-  p1 = tree.owls
-  P1 = as(tree.owls,"phylo4")
+
+  tree.owls <- read.tree(text="(((Strix_aluco:4.2,Asio_otus:4.2):3.1,Athene_noctua:7.3):6.3,Tyto_alba:13.5);")
+  P1 <- as(tree.owls, "phylo4")
   P1
-  sumryP1 = summary(P1)
-  sumryP1
+  summary(P1)
 
+
   ## summary of a polytomous tree
   E <- matrix(c(
-      8,  9, 
-      9, 10, 
-     10,  1, 
-     10,  2, 
-      9,  3, 
-      9,  4, 
-      8, 11, 
-     11,  5, 
-     11,  6, 
-     11,  7, 
-     NA,  8), ncol=2, byrow=TRUE) 
-  
+      8,  9,
+      9, 10,
+     10,  1,
+     10,  2,
+      9,  3,
+      9,  4,
+      8, 11,
+     11,  5,
+     11,  6,
+     11,  7,
+     NA,  8), ncol=2, byrow=TRUE)
+
   P2 <- phylo4(E)
   nodeLabels(P2) <- as.character(sort(nodeId(P2)))
   plot(P2, show.node.label=TRUE)

Modified: pkg/man/phylo4d.Rd
===================================================================
--- pkg/man/phylo4d.Rd	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/man/phylo4d.Rd	2009-04-22 15:42:53 UTC (rev 430)
@@ -80,8 +80,7 @@
   rows of data vs. number of nodes/tips/etc.)
 }
 \examples{
-library(ape)
-example(read.tree)
+tree.owls.bis <- read.tree(text = "((Strix_aluco:4.2,Asio_otus:4.2):3.1,Athene_noctua:7.3);")
 try(phylo4d(as(tree.owls.bis,"phylo4"),data.frame(wing=1:3)), silent=TRUE)
 obj <- phylo4d(as(tree.owls.bis,"phylo4"),data.frame(wing=1:3),
 use.tip.names=FALSE)

Modified: pkg/man/phylomat-class.Rd
===================================================================
--- pkg/man/phylomat-class.Rd	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/man/phylomat-class.Rd	2009-04-22 15:42:53 UTC (rev 430)
@@ -30,23 +30,23 @@
 }
 \author{Ben Bolker}
 \examples{
-  example("read.tree")
+   tree.owls <- read.tree(text="(((Strix_aluco:4.2,Asio_otus:4.2):3.1,Athene_noctua:7.3):6.3,Tyto_alba:13.5);")
   o2 <- as(tree.owls,"phylo4")
   ov <- as(o2,"phylo4vcov")
   o3 <- as(ov,"phylo4")
   ## these are not completely identical, but are
   ## topologically identical ...
-  
+
   ## edge matrices are in a different order:
   ## cf. o2 at edge and o3 at edge
   ## BUT the edge matrices are otherwise identical
   identical(o2 at edge[order(o2 at edge[,2]),],
             o3 at edge[order(o3 at edge[,2]),])
-  
+
   ## There is left/right ambiguity here in the tree orders:
   ## in o2 the 5->6->7->1 lineage
   ## (terminating in Strix aluco)
-  ## is first, in o3 the 5->6->3 lineage 
+  ## is first, in o3 the 5->6->3 lineage
   ## (terminating in Athene noctua) is first.
 
 }

Modified: pkg/man/subset-methods.Rd
===================================================================
--- pkg/man/subset-methods.Rd	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/man/subset-methods.Rd	2009-04-22 15:42:53 UTC (rev 430)
@@ -20,7 +20,7 @@
   for a tip index. With a \linkS4class{phylo4d} object
   'foo', \code{foo[i,j]} creates a subset of \code{foo} taking \code{i}
   for a tip index and \code{j} for the index of tips variables (see
-  details).\cr 
+  details).\cr
 }
 \section{Methods}{
   \describe{
@@ -58,7 +58,7 @@
   If \code{foo} is a \linkS4class{phylo4d} object, the index of
   variables ("j") is optional: \code{foo[i,j]} is the same as
   \code{foo[i]}.\cr
-  
+
 }
 \value{
   an object of class \code{"phylo4"}
@@ -72,7 +72,7 @@
 
 ## "subset" examples
 g1 <- as(geospiza,"phylo4")
-nodeLabels(g1) <- as.character(sort(nodeId(g1)))
+nodeLabels(g1) <- paste("N", nodeId(g1), sep="")
 plot(subset(g1,tips.exclude="scandens"))
 plot(subset(g1,mrca=c("scandens","fortis","pauper")))
 plot(subset(g1,node.subtree=18))
@@ -80,7 +80,7 @@
 ## "[" examples
 plot(g1,show.node.label=TRUE)
 plot(g1[c(1:6,14)],show.node.label=TRUE)
-nodeLabels(geospiza) <- as.character(sort(nodeId(geospiza)))
+nodeLabels(geospiza) <- paste("N", nodeId(geospiza))
 plot(geospiza[c(1:6,14)],show.node.label=TRUE)
 plot(geospiza[c(1:6,14),3:5],show.node.label=TRUE)
 }

Modified: pkg/tests/misctests.R
===================================================================
--- pkg/tests/misctests.R	2009-04-21 23:50:38 UTC (rev 429)
+++ pkg/tests/misctests.R	2009-04-22 15:42:53 UTC (rev 430)
@@ -68,13 +68,12 @@
 
 plot(p2,show.node.label=TRUE)
 
-library(ape)
-example(read.tree)
+tree.owls <- read.tree(text="(((Strix_aluco:4.2,Asio_otus:4.2):3.1,Athene_noctua:7.3):6.3,Tyto_alba:13.5);")
 
 z <- as(tree.owls,"phylo4")
 
 example("phylo4d")
-obj1 <- obj2 <- obj3 <- phylo4d(as(tree.owls,"phylo4"),data.frame(wing=1:4,color=factor(c("b","w","b","b")), tail=runif(4)*10), use.tip.names=FALSE)
+obj1 <- obj2 <- obj3 <- phylo4d(z, data.frame(wing=1:4,color=factor(c("b","w","b","b")), tail=runif(4)*10), use.tip.names=FALSE)
 
 obj2 at tip.data <- as.data.frame(obj2 at tip.data[,1])
 obj3 at tip.data <- cbind(obj1 at tip.data,obj2 at tip.data)



More information about the Phylobase-commits mailing list