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

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sun Jan 18 20:20:00 CET 2009


Author: jombart
Date: 2009-01-18 20:20:00 +0100 (Sun, 18 Jan 2009)
New Revision: 426

Modified:
   pkg/R/checkdata.R
   pkg/R/class-phylo4.R
   pkg/R/class-phylo4d.R
   pkg/R/methods-phylo4.R
   pkg/R/methods-phylo4d.R
   pkg/R/printphylo-deprecated.R
   pkg/R/setAs-Methods.R
   pkg/R/tbind.R
   pkg/R/treestruc.R
   pkg/R/treewalk.R
   pkg/inst/doc/phylobase.Rnw
   pkg/man/check.phylo4.Rd
   pkg/man/check.phylo4d.Rd
   pkg/man/hasSingles.Rd
   pkg/man/phylo4-class.Rd
   pkg/man/phylo4.Rd
   pkg/man/phylo4d-class.Rd
   pkg/man/phylo4d.Rd
   pkg/man/treewalk.Rd
   pkg/tests/misctests.R
   pkg/tests/phylotorture.R
Log:
Renamed some functions as follows:
from ->	to
attach_data	attachData
check_data	checkData
check_phylo4	checkPhylo4
check_tree	checkTree
getedges	getEdge
hasSingles	hasSingle




Modified: pkg/R/checkdata.R
===================================================================
--- pkg/R/checkdata.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/checkdata.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -1,10 +1,10 @@
 
 ## REQUIRED for all trees
-check_phylo4 <- function(object) {
-    check_tree(object)
+checkPhylo4 <- function(object) {
+    checkTree(object)
 }
 
-check_tree <- function(object,warn="retic",err=NULL) {
+checkTree <- function(object,warn="retic",err=NULL) {
     ## FIXME: check for cyclicity?
     nedges <- nrow(object at edge)
     if (hasEdgeLength(object)) {
@@ -102,7 +102,7 @@
     return(TRUE)
 }
 
-check_data <- function(object,
+checkData <- function(object,
                        label.type=c("row.names","column"),
                        label.column=1,
                        use.tip.names=TRUE,
@@ -374,7 +374,7 @@
     }
 }
 
-attach_data <- function(object,
+attachData <- function(object,
                         label.type=c("row.names","column"),
                         label.column=1,
                         use.tip.names=TRUE,
@@ -382,7 +382,7 @@
                         ...)
 {
 
-    ## assumes data have already been checked by check_data!
+    ## assumes data have already been checked by checkData!
     ## name matching default: use row.names of data frame
     label.type = match.arg(label.type)
     if (identical(label.type, "row.names")) {

Modified: pkg/R/class-phylo4.R
===================================================================
--- pkg/R/class-phylo4.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/class-phylo4.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -16,7 +16,7 @@
                         edge.label = character(0),
                         order = "unknown"
                        ),
-         validity = check_phylo4)
+         validity = checkPhylo4)
 
 #####################
 ## phylo4 constructor
@@ -79,9 +79,9 @@
     res at edge.label <- edge.label
     res at order <- order
 
-    ## check_phylo4 will return a character string if object is
+    ## checkPhylo4 will return a character string if object is
     ##  bad, otherwise TRUE
-    if (is.character(checkval <- check_phylo4(res))) stop(checkval)
+    if (is.character(checkval <- checkPhylo4(res))) stop(checkval)
     return(res)
 }
 

Modified: pkg/R/class-phylo4d.R
===================================================================
--- pkg/R/class-phylo4d.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/class-phylo4d.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -10,8 +10,8 @@
          ##all.data = data.frame(NULL) ),
          validity = function(object) {
              ## FIXME: finish this by intercepting FALSE, char string, etc.
-             check1 <- check_data(object)
-             check2 <- check_phylo4(object)
+             check1 <- checkData(object)
+             check2 <- checkPhylo4(object)
          },
          contains="phylo4")
 
@@ -43,7 +43,7 @@
            else return(TRUE)
        }
 
-       if(is.character(checkval <- check_phylo4(x))) stop(checkval)
+       if(is.character(checkval <- checkPhylo4(x))) stop(checkval)
 
        if(is.character(checkClass <- classData(all.data))) stop(checkClass)
        if(is.character(checkClass <- classData(tip.data))) stop(checkClass)
@@ -110,8 +110,8 @@
            }
        }
 
-       check_data(res, ...)
-       res <- attach_data(res,...)
+       checkData(res, ...)
+       res <- attachData(res,...)
        return(res)
 
 })

Modified: pkg/R/methods-phylo4.R
===================================================================
--- pkg/R/methods-phylo4.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/methods-phylo4.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -195,7 +195,7 @@
                       object
                   }
               })
-       if(is.character(checkval <- check_phylo4(ob)))
+       if(is.character(checkval <- checkPhylo4(ob)))
            stop(checkval)
        else
            return(ob)

Modified: pkg/R/methods-phylo4d.R
===================================================================
--- pkg/R/methods-phylo4d.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/methods-phylo4d.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -118,7 +118,7 @@
            tip = object at tip.data <- value,
            internal = object at node.data <- value,
            allnode = stop("for now, must set tip and node data separately"))
-    if(check_data(object, ...)) object <- attach_data(object, ...)
+    if(checkData(object, ...)) object <- attachData(object, ...)
     object
 })
 

Modified: pkg/R/printphylo-deprecated.R
===================================================================
--- pkg/R/printphylo-deprecated.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/printphylo-deprecated.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -10,21 +10,21 @@
               nb.node, "internal nodes\n"))
 
     ## print tip labels
-    cat("\nTip labels:\n")
+    cat("\nTips labels:\n")
     if (nb.tip > printlen) {
         cat(paste("\t", paste(x at tip.label[1:printlen], collapse = ", "),
                   ", ...\n", sep = ""))
     } else print(x at tip.label)
 
     ## print node labels
-    cat("\nNode labels:\n")
+    cat("\nNodes labels:\n")
     if (nb.node > printlen) {
         cat(paste("\t", paste(x at node.label[1:printlen], collapse = ", "),
                   ", ...\n", sep = ""))
     } else print(x at node.label)
 
     ## print edge labels
-    cat("\nEdge labels:\n")
+    cat("\nEdges labels:\n")
     if (nb.edge > printlen) {
         cat(paste("\t", paste(x at edge.label[1:printlen], collapse = ", "),
                   ", ...\n", sep = ""))

Modified: pkg/R/setAs-Methods.R
===================================================================
--- pkg/R/setAs-Methods.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/setAs-Methods.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -130,7 +130,7 @@
 #######################################################
 ## Exporting to dataframe
 setAs(from = "phylo4", to = "data.frame", def = function(from) {
-    if (is.character(checkval <- check_phylo4(from))) # check the phylo4
+    if (is.character(checkval <- checkPhylo4(from))) # check the phylo4
         stop(checkval)
     x <- from
     if (isRooted(x)) {
@@ -155,7 +155,7 @@
         }
         ## node and tip labels ##
         ## beware: they cannot be NULL
-        ## there are always tip labels (or check_phylo4 complains)
+        ## there are always tip labels (or checkPhylo4 complains)
         ## there may not be node labels (character(0))
         label <- labels(x,which="all")[nodeId(x,"all")]
         node.type <- nodeType(x)[node]
@@ -175,7 +175,7 @@
         }
         ## node and tip labels ##
         ## beware: they cannot be NULL
-        ## there are always tip labels (or check_phylo4 complains)
+        ## there are always tip labels (or checkPhylo4 complains)
         ## there may not be node labels (character(0))
         label <- labels(x,which="all")[node]
         node.type <- nodeType(x)[node]

Modified: pkg/R/tbind.R
===================================================================
--- pkg/R/tbind.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/tbind.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -2,13 +2,13 @@
 
 ## IF all missing data -- create multiPhylo4
 ## IF some have data -- create multiPhylo4d (user can coerce to multiPhylo4)
-## IF (check_data) then stop if all data not identical to first data
+## IF (checkData) then stop if all data not identical to first data
 ##
 ## need constructors for multiPhylo4, multiPhylo4d!!
 ## FIXME: need code to construct tree.names ...
 
 ## function to bind trees together into a multi-tree object
-tbind <- function(...,check_data=TRUE) {
+tbind <- function(...,checkData=TRUE) {
     L <- as.list(...)
     namevec <- names(L)
     treeclasses <- c("multiPhylo4d","multiPhylo4","phylo4","phylo4d")
@@ -33,7 +33,7 @@
     hasNodeData <- sapply(L[classes %in% tdataclasses],
                           function(x) {!is.null(x at node.data)})
     if (any(hasNodeData)) warning("internal node data discarded")
-    if (check_data) {
+    if (checkData) {
         ident <- sapply(alldat[-1],identical,y=alldat[[1]])
         if (!all(ident)) stop(paste("tip data sets differ"))
     } ## ?? implement code to check which ones differ (taking

Modified: pkg/R/treestruc.R
===================================================================
--- pkg/R/treestruc.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/treestruc.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -4,7 +4,7 @@
 ##  and that it's simple enough to do
 ##   any(edgeLength(x)==0) if necessary
 hasPoly <- function(object) {
-  if(!check_phylo4(object)) stop("to be used with a phylo4 object")
+  if(!checkPhylo4(object)) stop("to be used with a phylo4 object")
   degree <- tabulate(edges(object)[, 2])
   struc <- any(degree > 2)
   return(struc)
@@ -12,14 +12,14 @@
 
 
 
-hasSingles <- function(object) {
-  if(!check_phylo4(object)) stop("to be used with a phylo4 object")
+hasSingle <- function(object) {
+  if(!checkPhylo4(object)) stop("to be used with a phylo4 object")
   degree <- tabulate(na.omit(edges(object)[, 1]))
   any(degree == 1)
 }
 
 hasRetic <- function(object) {
-  if(!check_phylo4(object)) stop("to be used with a phylo4 object")
+  if(!checkPhylo4(object)) stop("to be used with a phylo4 object")
   ancest <- tabulate(edges(object)[, 2])
   any(ancest>1)
 }
@@ -29,8 +29,8 @@
 
 # Returns a vector of logical 
 # TRUE = this edge goes from an internal node to another
-#internEdge <- function(object){
-#  if(!check_phylo4(object)) stop("to be used with a phylo4 object")
+#internEdges <- function(object){
+#  if(!checkPhylo4(object)) stop("to be used with a phylo4 object")
 #  x <- object
 #  isTips <- (tabulate(x at edge[,1]) == 0)
 #  tips <- x at edge[isTips, 1]
@@ -40,12 +40,12 @@
 
 # Returns a vector of logical 
 # TRUE = this edge goes from an internal node to a tip
-#terminEdge <- function(object){
-#  return(!internEdge(object))
+#terminEdges <- function(object){
+#  return(!internEdges(object))
 #}
 
 #isPoly <- function(object, position=c("all", "terminal", "internal")){
-#  if(!check_phylo4(object)) stop("to be used with a phylo4 object")
+#  if(!checkPhylo4(object)) stop("to be used with a phylo4 object")
 #  x <- object
 #  pos <- match.arg(position)
 #  res <- (tabulate(x at edge[,1]) > 2)

Modified: pkg/R/treewalk.R
===================================================================
--- pkg/R/treewalk.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/R/treewalk.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -160,7 +160,7 @@
     ## FIXME: use extractTree if coming from phylo4d
 
     ## some checks
-    if (is.character(checkval <- check_phylo4(x))) stop(checkval)
+    if (is.character(checkval <- checkPhylo4(x))) stop(checkval)
     t1 <- getNode(x, node1)
     t2 <- getNode(x, node2)
     if(any(is.na(c(t1,t2)))) stop("wrong node specified")
@@ -191,15 +191,15 @@
 
 
 ###########
-# getedges
+# getEdge
 ###########
-getedges <- function(phy, node){
+getEdge <- function(phy, node){
 
     ## conversion from phylo, phylo4 and phylo4d
     x <- as(phy, "phylo4")
 
     ## come checks
-    if (is.character(checkval <- check_phylo4(x))) stop(checkval)
+    if (is.character(checkval <- checkPhylo4(x))) stop(checkval)
     node <- getNode(x, node)
     if(any(is.na(node))) stop("wrong node specified")
     root <- getNode(x, nTips(x)+1)
@@ -211,4 +211,4 @@
     names(res) <- names(node)
 
     return(res)
-} # end getedges
+} # end getEdge

Modified: pkg/inst/doc/phylobase.Rnw
===================================================================
--- pkg/inst/doc/phylobase.Rnw	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/inst/doc/phylobase.Rnw	2009-01-18 19:20:00 UTC (rev 426)
@@ -462,7 +462,7 @@
 \item all internal nodes [not including the root]
   must appear in the first (ancestor) column
   at least once [unlike \code{ape}, which nominally requires each internal node to have at least two descendants (although it doesn't
-absolutely prohibit them and has a \code{collapse.singles} function to get rid of them), \code{phylobase} does allow these ``singleton nodes'' and has a method \code{hasSingles} for detecting them].
+absolutely prohibit them and has a \code{collapse.singles} function to get rid of them), \code{phylobase} does allow these ``singleton nodes'' and has a method \code{hasSingle} for detecting them].
 Singleton nodes can be useful as a way of representing changes
 along a lineage; they are used this way in the \code{ouch} package.
 \item the number of occurrences of a node in the first column is related to the nature of the node: once if it is a singleton,

Modified: pkg/man/check.phylo4.Rd
===================================================================
--- pkg/man/check.phylo4.Rd	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/man/check.phylo4.Rd	2009-01-18 19:20:00 UTC (rev 426)
@@ -1,13 +1,13 @@
-\name{check_phylo4}
-\alias{check_phylo4}
-\alias{check_tree}
+\name{checkPhylo4}
+\alias{checkPhylo4}
+\alias{checkTree}
 \title{Validity checking for phylo4 objects}
 \description{
   Basic checks on the validity of S4 phylogenetic objects
 }
 \usage{
-check_phylo4(object)
-check_tree(object,warn="retic",err=NULL)
+checkPhylo4(object)
+checkTree(object,warn="retic",err=NULL)
 }
 \arguments{
   \item{object}{A prospective S4 object}
@@ -19,8 +19,8 @@
   As required by \code{\link{validObject}}, returns an
   error string (describing problems) or TRUE if everything is OK
 }
-\note{\code{check_phylo4} is an (inflexible) wrapper for
-  \code{check_tree}, which uses the default settings.
+\note{\code{checkPhylo4} is an (inflexible) wrapper for
+  \code{checkTree}, which uses the default settings.
   The rules for \code{phylo4} objects essentially follow
   those for \code{phylo} objects from the \code{ape} package,
   which are in turn defined in
@@ -36,7 +36,7 @@
 }
 \seealso{
   the \code{\link{phylo4}} constructor and \linkS4class{phylo4} class;
-  \code{\link{check_data}}, the \code{\link{phylo4d}} constructor and
+  \code{\link{checkData}}, the \code{\link{phylo4d}} constructor and
   the \linkS4class{phylo4d}
   class do checks for the data associated with trees.
   See \code{\link{coerce-methods}} for translation functions.

Modified: pkg/man/check.phylo4d.Rd
===================================================================
--- pkg/man/check.phylo4d.Rd	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/man/check.phylo4d.Rd	2009-01-18 19:20:00 UTC (rev 426)
@@ -1,20 +1,20 @@
-\name{check_phylo4d}
-\alias{check_data}
-\alias{attach_data}
+\name{checkPhylo4d}
+\alias{checkData}
+\alias{attachData}
 \title{Validity checking for phylo4d objects}
 \description{
   Basic checks on the validity of S4 phylogenetic plus data objects
   (i.e. \linkS4class{phylo4d} objects).
 }
 \usage{
-check_data(object, label.type = c("row.names", "column"),
+checkData(object, label.type = c("row.names", "column"),
 label.column = 1, use.tip.names=TRUE, missing.tip.data=c("fail","OK","warn"),
 extra.tip.data=c("fail","OK","warn"), default.tip.names=c("warn","OK","fail"),
 use.node.names=FALSE, missing.node.data=c("OK","warn","fail"),
 extra.node.data=c("OK","warn","fail"), default.node.names=c("warn","OK","fail"),
 non.unique.tips=c("warn", "OK", "fail"), non.unique.nodes=c("warn", "OK", "fail"), \dots)
 
-attach_data(object, label.type = c("row.names", "column"), label.column = 1,
+attachData(object, label.type = c("row.names", "column"), label.column = 1,
 use.tip.names = TRUE, use.node.names = FALSE,\dots)
 }
 
@@ -39,14 +39,14 @@
   \item{\dots}{Further arguments (for consistency)}
 }
 \value{
-  \code{check_data} returns an error string (describing problems) or \code{TRUE} if everything is OK. If option \code{fail} is specified and a problem is encountered, returns an error string. If option \code{warn} is specified and a problem is encountered, returns \code{TRUE} plus a warning message.
+  \code{checkData} returns an error string (describing problems) or \code{TRUE} if everything is OK. If option \code{fail} is specified and a problem is encountered, returns an error string. If option \code{warn} is specified and a problem is encountered, returns \code{TRUE} plus a warning message.
 
   By default, tip data names are used to attach the tip data to the tree, must be present, and must match the set of tree taxa exactly. By default node data names are not used to attach the data to the tree, and thus node data names are not required.
 
-  \code{attach_data} returns the phylo4 object with tipdata and nodedata (if present) attached to the phylo4 tree.
+  \code{attachData} returns the phylo4 object with tipdata and nodedata (if present) attached to the phylo4 tree.
 }
 \details{
-  \code{check_data} checks validity of a phylo4d object. For tipdata and nodedata, checks
+  \code{checkData} checks validity of a phylo4d object. For tipdata and nodedata, checks
   for presence of tip and node names, whether tip or node data taxa and tree taxa are an
   exact match, and whether tip or node data taxa are a superset or subset of the tree
   taxa. By default, if several tip or node labels are non-unique, they all receive the same
@@ -54,9 +54,9 @@
   this behavior by changing the value of the arguments \code{non.unique.tips} and
   \code{non.unique.nodes} to \code{fail}.
 
-  \code{attach_data} takes a phylo4d object that has been checked, and attaches the tipdata and nodedata to the object. This involves the data being subset to include only the taxa present in the tree, with missing data taxa assigned NA values. The data are sorted to match the order of the tip.labels of the tree to allow use with comparative analysis functions.
+  \code{attachData} takes a phylo4d object that has been checked, and attaches the tipdata and nodedata to the object. This involves the data being subset to include only the taxa present in the tree, with missing data taxa assigned NA values. The data are sorted to match the order of the tip.labels of the tree to allow use with comparative analysis functions.
 }
-\seealso{the \code{\link{phylo4d}} constructor, the \linkS4class{phylo4d} class. See also the \code{\link{check_phylo4}}, the \code{\link{phylo4}} constructor and the \linkS4class{phylo4} class. See \code{\link{coerce-methods}} for translation functions.}
+\seealso{the \code{\link{phylo4d}} constructor, the \linkS4class{phylo4d} class. See also the \code{\link{checkPhylo4}}, the \code{\link{phylo4}} constructor and the \linkS4class{phylo4} class. See \code{\link{coerce-methods}} for translation functions.}
 \author{Steven Kembel \email{skembel at berkeley.edu}}
 \examples{
 require(ape)
@@ -73,7 +73,7 @@
 
 #create phylo4d objects with tip data
 p4d <- phylo4d(p4, dat)
-check_data(p4d)
+checkData(p4d)
 p4d.sorted <- phylo4d(p4, dat[5:1, ])
 try(p4d.nonames <- phylo4d(p4, dat.defaultnames))
 p4d.nonames <- phylo4d(p4, dat.defaultnames, use.tip.names = FALSE)

Modified: pkg/man/hasSingles.Rd
===================================================================
--- pkg/man/hasSingles.Rd	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/man/hasSingles.Rd	2009-01-18 19:20:00 UTC (rev 426)
@@ -1,5 +1,5 @@
-\name{hasSingles}
-\alias{hasSingles}
+\name{hasSingle}
+\alias{hasSingle}
 \alias{hasPoly}
 \alias{hasRetic}
 \title{Test trees for polytomies, inline nodes,
@@ -10,7 +10,7 @@
   (i.e., nodes with more than one ancestor)
 }
 \usage{
-hasSingles(object)
+hasSingle(object)
 hasPoly(object)
 hasRetic(object)
 }
@@ -38,6 +38,6 @@
 example(read.tree)
 owls4 = as(tree.owls.bis, "phylo4")
 hasPoly(owls4)
-hasSingles(owls4)
+hasSingle(owls4)
 }
 \keyword{misc}

Modified: pkg/man/phylo4-class.Rd
===================================================================
--- pkg/man/phylo4-class.Rd	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/man/phylo4-class.Rd	2009-01-18 19:20:00 UTC (rev 426)
@@ -71,7 +71,7 @@
    The \code{names} method returns a vector of characters corresponding
    to the names of the slots.
   }
-\seealso{the \code{\link{phylo4}} constructor, the \code{\link{check_phylo4}}
+\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}   
 \examples{

Modified: pkg/man/phylo4.Rd
===================================================================
--- pkg/man/phylo4.Rd	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/man/phylo4.Rd	2009-01-18 19:20:00 UTC (rev 426)
@@ -27,7 +27,7 @@
 \author{phylobase team}
 \note{Translation functions are available from many valid tree formats. See \link{coerce-methods}.  
 }
-\seealso{\code{\link{coerce-methods}} for translation functions. The \linkS4class{phylo4} class, the \code{\link{check_data}}
+\seealso{\code{\link{coerce-methods}} for translation functions. The \linkS4class{phylo4} class, the \code{\link{checkData}}
   function to check the validity of \code{phylo4} objects. See also the \code{\link{phylo4d}} constructor, and \linkS4class{phylo4d} class.}
 \examples{
 # a three species tree:

Modified: pkg/man/phylo4d-class.Rd
===================================================================
--- pkg/man/phylo4d-class.Rd	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/man/phylo4d-class.Rd	2009-01-18 19:20:00 UTC (rev 426)
@@ -61,7 +61,7 @@
    The \code{names} method returns a vector of characters corresponding
    to the names of the slots.
   }
-\seealso{\code{\link{coerce-methods}} for translation functions. The \code{\link{phylo4d}} constructor and the \code{\link{check_data}} function to check the validity of trees and data. See also the \code{\link{phylo4}} constructor, the \linkS4class{phylo4} class, and the \code{\link{check_phylo4}} function to check the validity of \code{phylo4} trees. }
+\seealso{\code{\link{coerce-methods}} for translation functions. The \code{\link{phylo4d}} constructor and the \code{\link{checkData}} function to check the validity of trees and data. See also the \code{\link{phylo4}} constructor, the \linkS4class{phylo4} class, and the \code{\link{checkPhylo4}} function to check the validity of \code{phylo4} trees. }
 \author{Ben Bolker, Thibaut Jombart}   
 \examples{
   library(ape)

Modified: pkg/man/phylo4d.Rd
===================================================================
--- pkg/man/phylo4d.Rd	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/man/phylo4d.Rd	2009-01-18 19:20:00 UTC (rev 426)
@@ -44,7 +44,7 @@
     trait. This argument is evaluated only if both \code{tip.data} and
     \code{node.data} have identical column names.}
   \item{\dots}{further arguments to be passed to other methods. Used to
-    control the validity checking of the created object (see \code{\link{check_data}}).}
+    control the validity checking of the created object (see \code{\link{checkData}}).}
 }
 
 \details{
@@ -68,7 +68,7 @@
 
 \seealso{
 \code{\link{coerce-methods}} for translation functions. The
-  \linkS4class{phylo4d} class, the \code{\link{check_data}}
+  \linkS4class{phylo4d} class, the \code{\link{checkData}}
   function to check the validity of \code{phylo4d} objects;
   \linkS4class{phylo4} class and \link{phylo4} constructor.}
 

Modified: pkg/man/treewalk.Rd
===================================================================
--- pkg/man/treewalk.Rd	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/man/treewalk.Rd	2009-01-18 19:20:00 UTC (rev 426)
@@ -6,7 +6,7 @@
 \alias{siblings}
 \alias{MRCA}
 \alias{getNode}
-\alias{getedges}
+\alias{getEdge}
 \alias{shortestPath}
 \alias{sumEdgeLength}
 \alias{sumEdgeLength,phylo4-method}
@@ -51,7 +51,7 @@
   \item{\code{getNode}}{takes character strings corresponding to tip
     or node labels, or node numbers; it returns a named
     vector of node numbers}
-  \item{\code{getedges}}{takes character strings naming terminal
+  \item{\code{getEdge}}{takes character strings naming terminal
     node of edges, or the corresponding node numbers; it returns a named
     vector of edge numbers.}
   \item{\code{ancestors} and \code{descendants}}{
@@ -94,7 +94,7 @@
   shortestPath(geospiza, "F","L")
 
   ## identifying an edge from its terminal node
-  getedges(geospiza,c("olivacea","B","fortis"))
+  getEdge(geospiza,c("olivacea","B","fortis"))
   getNode(geospiza, c("olivacea","B","fortis"))
   geospiza at edge[c(26,1,11),]
   ## FIXME

Modified: pkg/tests/misctests.R
===================================================================
--- pkg/tests/misctests.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/tests/misctests.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -7,7 +7,7 @@
 ## push data back into list form as in geiger
 
 t1 <-  try(p1 <- phylo4d(geospiza0$geospiza.tree,geospiza0$geospiza.data))
-## Error in check_data(res, ...) :
+## Error in checkData(res, ...) :
 ##   Tip data names are a subset of tree tip labels.
 
 p2 <- as(geospiza0$geospiza.tree,"phylo4")

Modified: pkg/tests/phylotorture.R
===================================================================
--- pkg/tests/phylotorture.R	2009-01-14 20:57:56 UTC (rev 425)
+++ pkg/tests/phylotorture.R	2009-01-18 19:20:00 UTC (rev 426)
@@ -18,7 +18,7 @@
     p2 <- p1[OKvals]
     length(p2)
     has.poly <- sapply(p2,hasPoly)
-    has.sing <- sapply(p2,hasSingles)
+    has.sing <- sapply(p2,hasSingle)
     has.retic <- sapply(p2,hasRetic)   
     ##
     if (any(has.sing)) {



More information about the Phylobase-commits mailing list