[Phylobase-commits] r124 - pkg/R

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Feb 26 17:58:18 CET 2008


Author: jombart
Date: 2008-02-26 17:58:18 +0100 (Tue, 26 Feb 2008)
New Revision: 124

Modified:
   pkg/R/phylo4.R
   pkg/R/plot.R
Log:
nTips now uses the edge matrix to determine tips instead of labels (check uses comparison: nTips(x)==length(x$tip.label)


Modified: pkg/R/phylo4.R
===================================================================
--- pkg/R/phylo4.R	2008-02-26 15:27:51 UTC (rev 123)
+++ pkg/R/phylo4.R	2008-02-26 16:58:18 UTC (rev 124)
@@ -49,7 +49,10 @@
     standardGeneric("nTips")
 })
 setMethod("nTips","phylo4", function(x,...) {
-    length(x at tip.label)
+    ## length(x at tip.label)
+    E <- edges(x)
+    res <- sum(!E[,2] %in% E[,1])
+    return(res)
 })
 ## rm(nTips)
 
@@ -585,7 +588,7 @@
 ## TEST ME . wait for validity check
 ##
 phylo4 <- function(edge, edge.length=NULL, tip.label=NULL, node.label=NULL,
-                   edge.label=NULL, root.edge=NULL,...){
+                   edge.label=NULL, root.edge=NULL, ...){
     ## edge
     mode(edge) <- "integer"
     if(any(is.na(edge))) stop("NA are not allowed in edge matrix")
@@ -624,7 +627,7 @@
         edge.label <- paste("E", edge[,2], sep="")
     } else {
         if(length(edge.label) != nrow(edge)) stop("the edge labels are not consistent with the number of edges")
-    } 
+    }
 
     ## root.edge - if no root edge lenth provided, set to a numeric NA
     if(is.null(root.edge)) root.edge <- as.numeric(NA)
@@ -669,7 +672,7 @@
 ## first arg is a phylo4
 setMethod("phylo4d", c("phylo4"), function(x, tip.data=NULL, node.data=NULL, all.data=NULL, ...){
 
-    if(!check_phylo4(x)) stop("invalid phylo4 object provided in x")
+    if(is.character(checkval <- check_phylo4(x))) stop(checkval)
     
     res <- new("phylo4d")
     res at edge <- x at edge

Modified: pkg/R/plot.R
===================================================================
--- pkg/R/plot.R	2008-02-26 15:27:51 UTC (rev 123)
+++ pkg/R/plot.R	2008-02-26 16:58:18 UTC (rev 124)
@@ -12,6 +12,7 @@
 
 setGeneric("plot")
 setMethod("plot",signature(x="phylo4",y="missing"), function(x,...){
+    invisible(check_phylo4(x))
     if(!require(ape)) stop("the ape package is required")
     x <- as(x, "phylo")
     plot(x, ...)
@@ -27,10 +28,10 @@
 ################
 setMethod("plot", signature(x="phylo4d",y="missing"), 
           function(x, treetype=c("phylogram","cladogram"), symbol=c("circles", "squares"), center=TRUE, scale=TRUE, legend=TRUE, grid=TRUE, box=TRUE, show.tip.label=TRUE, show.node.label=TRUE, show.var.label=TRUE, ratio.tree=1/3, font=3, tip.label=x at tip.label, var.label=colnames(x at tip.data), cex.symbol=1, cex.label=1, cex.legend=1, ...){
-
               
     #### preliminary stuff and checks
-    if(!require(ape)) stop("the ape package is required")   
+    invisible(check_phylo4d(x))
+    if(!require(ape)) stop("the ape package is required")
     ## if(ncol(tdata(x,which="tip")) == 0) stop("no data in this phylo4d object")
     
     cex <- par("cex")



More information about the Phylobase-commits mailing list