[Phylobase-commits] r878 - pkg/R

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Mar 17 14:18:21 CET 2014


Author: francois
Date: 2014-03-17 14:18:21 +0100 (Mon, 17 Mar 2014)
New Revision: 878

Added:
   pkg/R/phylobase-package.R
Modified:
   pkg/R/checkdata.R
   pkg/R/class-phylo4.R
   pkg/R/class-phylo4d.R
   pkg/R/class-phylomats.R
   pkg/R/formatData.R
   pkg/R/methods-multiphylo4.R
   pkg/R/methods-phylo4.R
   pkg/R/methods-phylo4d.R
   pkg/R/phylobase.options.R
   pkg/R/readNCL.R
   pkg/R/setAs-Methods.R
   pkg/R/subset.R
   pkg/R/tbind.R
   pkg/R/treePlot.R
   pkg/R/treestruc.R
   pkg/R/treewalk.R
   pkg/R/zzz.R
Log:
transfered doc to roxygen format (not tested if it compiles) + cleanup

Modified: pkg/R/checkdata.R
===================================================================
--- pkg/R/checkdata.R	2014-03-17 13:15:09 UTC (rev 877)
+++ pkg/R/checkdata.R	2014-03-17 13:18:21 UTC (rev 878)
@@ -1,4 +1,48 @@
 ## REQUIRED for all trees
+
+
+#' Validity checking for phylo4 objects
+#' 
+#' Basic checks on the validity of S4 phylogenetic objects
+#' 
+#' 
+#' @aliases checkPhylo4 checkTree checkPhylo4Data
+#' @param object A prospective phylo4 or phylo4d object
+#' @return As required by \code{\link[methods]{validObject}}, returns an error
+#' string (describing problems) or TRUE if everything is OK.
+#' @note
+#' 
+#' These functions are only intended to be called by other phylobase functions.
+#' 
+#' \code{checkPhylo4} is an (inflexible) wrapper for \code{checkTree}.  The
+#' rules for \code{phylo4} objects essentially follow those for \code{phylo}
+#' objects from the \code{ape} package, which are in turn defined in
+#' \url{http://ape.mpl.ird.fr/misc/FormatTreeR_28July2008.pdf}.  These are
+#' essentially that: \itemize{ \item if the tree has edge lengths defined, the
+#' number of edge lengths must match the number of edges; \item the number of
+#' tip labels must match the number of tips; \item in a tree with \code{ntips}
+#' tips and \code{nnodes} (total) nodes, nodes 1 to \code{ntips} must be tips
+#' \item if the tree is rooted, the root must be node number \code{ntips+1} and
+#' the root node must be the first row of the edge matrix \item tip labels,
+#' node labels, edge labels, edge lengths must have proper internal names (i.e.
+#' internal names that match the node numbers they document) \item tip and node
+#' labels must be unique }
+#' 
+#' You can alter some of the default options by using the function
+#' \code{phylobase.options}.
+#' 
+#' For \code{phylo4d} objects, \code{checkTree} also calls
+#' \code{checkPhylo4Data} to check the validity of the data associated with the
+#' tree. It ensures that (1) the data associated with the tree have the correct
+#' dimensions, (2) that the row names for the data are correct.
+#' @author Ben Bolker, Steven Kembel, Francois Michonneau
+#' @seealso the \code{\link{phylo4}} constructor and \linkS4class{phylo4}
+#' class; \code{\link{formatData}}, 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 and
+#' \code{\link{phylobase.options} to change some of the default options of the
+#' validator.}
+#' @keywords misc
 checkPhylo4 <- function(object) {
     ct <- checkTree(object)
 

Modified: pkg/R/class-phylo4.R
===================================================================
--- pkg/R/class-phylo4.R	2014-03-17 13:15:09 UTC (rev 877)
+++ pkg/R/class-phylo4.R	2014-03-17 13:18:21 UTC (rev 878)
@@ -1,3 +1,20 @@
+#' The phylo4 class
+#' 
+#' Classes for phylogenetic trees
+#' 
+#' 
+#' @name phylo4-class
+#' @aliases phylo4_orderings phylo-class phylo4-class
+#' @docType class
+#' @section Objects from the Class: Phylogenetic tree objects can be created by
+#' calls to the \code{\link{phylo4}} constructor function.  Translation
+#' functions from other phylogenetic packages are also available. See
+#' \code{\link{coerce-methods}}.
+#' @author Ben Bolker, Thibaut Jombart
+#' @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.
+#' @keywords classes
 setClass("phylo4",
          representation(edge = "matrix",
                         edge.length = "numeric",
@@ -95,6 +112,84 @@
 ## phylo4 constructor
 #####################
 
+
+#' Create a phylogenetic tree
+#' 
+#' \code{phylo4} is a generic constructor that creates a phylogenetic tree
+#' object for use in phylobase methods. Phylobase contains functions for input
+#' of phylogenetic trees and data, manipulation of these objects including
+#' pruning and subsetting, and plotting. The phylobase package also contains
+#' translation functions to forms used in other comparative phylogenetic method
+#' packages.
+#' 
+#' The minimum information necessary to create a phylobase tree object is a
+#' valid edge matrix. The edge matrix describes the topology of the phylogeny.
+#' Each row describes a branch of the phylogeny, with the (descendant) node
+#' number in column 2 and its ancestor's node number in column 1. These numbers
+#' are used internally and must be unique for each node.
+#' 
+#' The labels designate either nodes or edges. The vector \code{node.label}
+#' names internal nodes, and together with \code{tip.label}, name all nodes in
+#' the tree. The vector \code{edge.label} names all branches in the tree. All
+#' label vectors are optional, and if they are not given, internally-generated
+#' labels will be assigned. The labels, whether user-specified or internally
+#' generated, must be unique as they are used to join species data with
+#' phylogenetic trees.
+#' 
+#' @name phylo4-methods
+#' @aliases phylo4 phylo4-methods phylo4,matrix-method phylo4,phylo-method
+#' @docType methods
+#' @param x a matrix of edges or an object of class \code{phylo} (see above)
+#' @param edge A numeric, two-column matrix with as many rows as branches in
+#' the phylogeny.
+#' @param edge.length Edge (branch) length. (Optional)
+#' @param tip.label A character vector of species names (names of "tip" nodes).
+#' (Optional)
+#' @param node.label A character vector of internal node names. (Optional)
+#' @param edge.label A character vector of edge (branch) names. (Optional)
+#' @param order character: tree ordering (allowable values are listed in
+#' \code{phylo4_orderings}, currently "unknown", "preorder" (="cladewise" in
+#' \code{ape}), and "postorder", with "cladewise" and "pruningwise" also
+#' allowed for compatibility with \code{ape})
+#' @param check.node.labels if \code{x} is of class \code{phylo}, either "keep"
+#' (the default) or "drop" node labels. This argument is useful if the
+#' \code{phylo} object has non-unique node labels.
+#' @param annote any additional annotation data to be passed to the new object
+#' @note Translation functions are available from many valid tree formats. See
+#' \link{coerce-methods}.
+#' @section Methods: \describe{ \item{x = "matrix"}{creates a phylobase tree
+#' from a matrix of edges}
+#' 
+#' \item{x = "phylo"}{creates a phylobase tree from an object of class
+#' \code{phylo}} }
+#' @author phylobase team
+#' @seealso \code{\link{coerce-methods}} for translation functions. The
+#' \linkS4class{phylo4} class, the \code{\link{formatData}} function to check
+#' the validity of \code{phylo4} objects. See also the \code{\link{phylo4d}}
+#' constructor, and \linkS4class{phylo4d} class.
+#' @keywords classes
+#' @examples
+#' 
+#' # a three species tree:
+#' mytree <- phylo4(x=matrix(data=c(4,1, 4,5, 5,2, 5,3, 0,4), ncol=2,
+#' byrow=TRUE), tip.label=c("speciesA", "speciesB", "speciesC")) 
+#' mytree
+#' plot(mytree)
+#' 
+#' # another way to specify the same tree:
+#' mytree <- phylo4(x=cbind(c(4, 4, 5, 5, 0), c(1, 5, 2, 3, 4)),
+#' tip.label=c("speciesA", "speciesB", "speciesC")) 
+#' 
+#' # another way:
+#' mytree <- phylo4(x=rbind(c(4, 1), c(4, 5), c(5, 2), c(5, 3), c(0, 4)),
+#' tip.label=c("speciesA", "speciesB", "speciesC")) 
+#' 
+#' # with branch lengths:
+#' mytree <- phylo4(x=rbind(c(4, 1), c(4, 5), c(5, 2), c(5, 3), c(0, 4)),
+#' tip.label=c("speciesA", "speciesB", "speciesC"), edge.length=c(1, .2,
+#' .8, .8, NA))
+#' plot(mytree)
+#' 
 ## generic
 setGeneric("phylo4", function(x, ...) { standardGeneric("phylo4")} )
 

Modified: pkg/R/class-phylo4d.R
===================================================================
--- pkg/R/class-phylo4d.R	2014-03-17 13:15:09 UTC (rev 877)
+++ pkg/R/class-phylo4d.R	2014-03-17 13:18:21 UTC (rev 878)
@@ -1,6 +1,7 @@
 ###################################
 ## phylo4d class
 ## extend: phylo with data
+#' phylo4d class
 setClass("phylo4d",
          representation(data="data.frame",
                         metadata = "list"),
@@ -15,6 +16,32 @@
 ######################
 ## phylo4d constructor
 ######################
+
+#' phylo4d class
+#' 
+#' S4 class for phylogenetic tree and data.
+#' 
+#' 
+#' @name phylo4d-class
+#' @docType class
+#' @section Objects from the Class: Objects can be created from various trees
+#' and a data.frame using the constructor \code{phylo4d}, or using
+#' \code{new("phylo4d", \dots{})} for empty objects.
+#' @author Ben Bolker, Thibaut Jombart
+#' @seealso \code{\link{coerce-methods}} for translation functions. The
+#' \code{\link{phylo4d}} constructor and the \code{\link{formatData}} 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.
+#' @keywords classes
+#' @examples
+#'   example(read.tree, "ape")
+#'   obj <- phylo4d(as(tree.owls.bis,"phylo4"), data.frame(wing=1:3))
+#'   obj
+#'   names(obj)
+#'   summary(obj)
+
 ## TEST ME
 ## '...' recognized args for data are tipdata and nodedata.
 ## other recognized options are those known by the phylo4 constructor

Modified: pkg/R/class-phylomats.R
===================================================================
--- pkg/R/class-phylomats.R	2014-03-17 13:15:09 UTC (rev 877)
+++ pkg/R/class-phylomats.R	2014-03-17 13:18:21 UTC (rev 878)
@@ -1,4 +1,45 @@
 
+#' matrix classes for phylobase
+#' 
+#' Classes representing phylogenies as matrices
+#' 
+#' 
+#' @name phylomat-class
+#' @aliases phylo4vcov-class as_phylo4vcov
+#' @docType class
+#' @param from a \code{phylo4} object
+#' @param \dots optional arguments, to be passed to \code{vcov.phylo} in
+#' \code{ape} (the main useful option is \code{cor}, which can be set to
+#' \code{TRUE} to compute a correlation rather than a variance-covariance
+#' matrix)
+#' @section Objects from the Class: These are square matrices (with rows and
+#' columns corresponding to tips, and internal nodes implicit) with different
+#' meanings depending on the type (variance-covariance matrix, distance matrix,
+#' etc.).
+#' @author Ben Bolker
+#' @keywords classes
+#' @examples
+#' 
+#'   tree.owls <- ape::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
+#'   ## (terminating in Athene noctua) is first.
+#' 
+#' 
 ## define class for phylogenetic var-cov matrices
 setClass("phylo4vcov",
          representation("matrix",

Modified: pkg/R/formatData.R
===================================================================
--- pkg/R/formatData.R	2014-03-17 13:15:09 UTC (rev 877)
+++ pkg/R/formatData.R	2014-03-17 13:18:21 UTC (rev 878)
@@ -1,3 +1,58 @@
+#' Format data for use in phylo4d objects
+#' 
+#' Associates data with tree nodes and applies consistent formatting rules.
+#' 
+#' 
+#' \code{formatData} is an internal function that should not be called directly
+#' by the user. It is used to format data provided by the user before
+#' associating it with a tree, and is called internally by the \code{phylo4d},
+#' \code{tdata}, and \code{addData} methods. However, users may pass additional
+#' arguments to these methods in order to control how the data are matched to
+#' nodes.
+#' 
+#' Rules for matching rows of data to tree nodes are determined jointly by the
+#' \code{match.data} and \code{rownamesAsLabels} arguments. If
+#' \code{match.data} is TRUE, data frame rows will be matched exclusively
+#' against tip and node labels if \code{rownamesAsLabels} is also TRUE, whereas
+#' any all-digit row names will be matched against tip and node numbers if
+#' \code{rownamesAsLabels} is FALSE (the default). If \code{match.data} is
+#' FALSE, \code{rownamesAsLabels} has no effect, and row matching is purely
+#' positional with respect to the order returned by \code{nodeId(phy, type)}.
+#' 
+#' \code{formatData} (1) converts labels provided in the data into node
+#' numbers, (2) makes sure that the data are appropriately matched against tip
+#' and/or internal nodes, (3) checks for differences between data and tree, (4)
+#' creates a data frame with the correct dimensions given a tree.
+#' 
+#' @param phy a valid \code{phylo4} object
+#' @param dt a data frame, matrix, vector, or factor
+#' @param type type of data to attach
+#' @param match.data (logical) should the rownames of the data frame be used to
+#' be matched against tip and internal node identifiers? See details.
+#' @param rownamesAsLabels (logical), should the row names of the data provided
+#' be matched only to labels (TRUE), or should any number-like row names be
+#' matched to node numbers (FALSE and default)
+#' @param label.type character, \code{rownames} or \code{column}: should the
+#' labels be taken from the row names of \code{dt} or from the
+#' \code{label.column} column of \code{dt}?
+#' @param label.column if \code{label.type=="column"}, column specifier (number
+#' or name) of the column containing tip labels
+#' @param missing.data action to take if there are missing data or if there are
+#' data labels that don't match
+#' @param extra.data action to take if there are extra data or if there are
+#' labels that don't match
+#' @param keep.all (logical), should the returned data have rows for all nodes
+#' (with NA values for internal rows when type='tip', and vice versa) (TRUE and
+#' default) or only rows corresponding to the type argument
+#' @return \code{formatData} returns a data frame having node numbers as row
+#' names. The data frame is also formatted to have the correct dimension given
+#' the \code{phylo4} object provided.
+#' @author Francois Michonneau
+#' @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.
+#' @keywords misc
 formatData <- function(phy, dt, type=c("tip", "internal", "all"),
                        match.data=TRUE, rownamesAsLabels=FALSE,
                        label.type=c("rownames", "column"),

Modified: pkg/R/methods-multiphylo4.R
===================================================================
--- pkg/R/methods-multiphylo4.R	2014-03-17 13:15:09 UTC (rev 877)
+++ pkg/R/methods-multiphylo4.R	2014-03-17 13:18:21 UTC (rev 878)
@@ -0,0 +1,11 @@
+
+#' multiPhylo4 and extended classes
+#' 
+#' Classes for lists of phylogenetic trees.  These classes and methods are
+#' planned for a future version of \code{phylobase}.
+#' 
+#' 
+#' @name multiPhylo-class
+#' @aliases multiPhylo-class multiPhylo4-class multiPhylo4d-class tbind
+#' @docType class
+#' @keywords classes

Modified: pkg/R/methods-phylo4.R
===================================================================
--- pkg/R/methods-phylo4.R	2014-03-17 13:15:09 UTC (rev 877)
+++ pkg/R/methods-phylo4.R	2014-03-17 13:18:21 UTC (rev 878)
@@ -54,6 +54,75 @@
 ### 8. Tree properties
 ###  8.1. isUltrametric()
 
+#' 
+#' @name phylo4-accessors
+#' @aliases nNodes nNodes-methods nNodes,phylo4-method nTips nTips-methods
+#' nTips,phylo4-method nTips,phylo-method depthTips depthTips-methods
+#' depthTips,phylo4-method depthTips,phylo4d-method edges edges-methods
+#' edges,phylo4-method nEdges nEdges-methods nEdges,phylo4-method nodeDepth
+#' nodeDepth-methods nodeDepth,phylo4-method edgeOrder edgeOrder,phylo4-method
+#' hasEdgeLength hasEdgeLength-methods hasEdgeLength,phylo4-method edgeLength
+#' edgeLength-methods edgeLength,phylo4-method edgeLength<-
+#' edgeLength<-,phylo4-method edgeLength<-,phylo4,ANY-method nodeType
+#' nodeType,phylo4-method isRooted isRooted-methods isRooted,phylo4-method
+#' rootEdge rootEdge-methods rootEdge,phylo4-method rootNode rootNode-methods
+#' rootNode,phylo4-method rootNode<- rootNode<-,phylo4-method isUltrametric
+#' isUltrametric-methods isUltrametric,phylo4-method
+#' @docType methods
+#' @param x a phylo4/phylo4d object
+#' @param node which edge to extract (indexed by descendant node)
+#' @param value a vector of edge lengths or a node number
+#' @param use.names Should the names of \code{value} be used to match edge
+#' lengths provided?
+#' @param drop.root logical: drop root row from edge matrix?
+#' @param tol tolerance in rounding error to determine whether the tree is
+#' ultrametric
+#' @param \dots additional parameters passed (currently ignored)
+#' @section Methods: \describe{ \item{nTips}{\code{signature(object="phylo4")}:
+#' number of tips}
+#' 
+#' \item{depthTips}{\code{signature(object="phylo4")}: distance between the
+#' tips and the root}
+#' 
+#' \item{nNodes}{\code{signature(object="phylo4")}: number of internal nodes}
+#' 
+#' \item{nEdges}{\code{signature(object = "phylo4")}: number of edges}
+#' 
+#' \item{edges}{\code{signature(object = "phylo4")}: returns the edge matrix}
+#' 
+#' \item{edgeOrder}{\code{signature(object = "phylo4")}: returns the order in
+#' which the edges are stored}
+#' 
+#' \item{hasEdgeLength}{\code{signature(object = "phylo4")}: whether tree has
+#' edge (branch) lengths}
+#' 
+#' \item{edgeLength}{\code{signature(object = "phylo4")}: edge (branch) lengths
+#' (or NAs if missing) ordered according to the edge matrix}
+#' 
+#' \item{nodeType}{\code{signature(object = "phylo4")}: named vector which has
+#' the type of node (internal, tip, root) for value, and the node number for
+#' name}
+#' 
+#' \item{nodeDepth}{\code{signature(object = "phylo4")}: named vector which
+#' gives the distance between nodes and the root}
+#' 
+#' \item{isRooted}{\code{signature(object = "phylo4")}: whether tree is rooted
+#' (i.e. has explicit root edge defined \emph{or} root node has <= 2
+#' descendants)}
+#' 
+#' \item{rootEdge}{\code{signature(object = "phylo4")}: root edge}
+#' 
+#' \item{isUltrametric}{\code{signature(object = "phylo4")}: whether the tree
+#' is ultrametric} }
+#' @keywords methods
+#' @examples
+#' 
+#' data(geospiza)
+#' edgeLength(geospiza, 5)
+#' edgeLength(geospiza, "olivacea")
+#' edgeLength(geospiza, 5:7)
+#' 
+
 #########################################################
 ### Tip accessors
 #########################################################
@@ -142,6 +211,24 @@
 
 })
 
+## nodeId
+setGeneric("nodeIdCpp", function(x, type=c("all", "tip", "internal",
+    "root")) {
+    standardGeneric("nodeIdCpp")
+})
+
+setMethod("nodeIdCpp", signature(x="phylo4"),
+          function(x, type=c("all", "tip", "internal", "root")) {
+              type <- match.arg(type)
+              E <- edges(x)
+              nid <- switch(type,
+                            all = getAllNodesFast(x at edge, isRooted(x)),
+                            tip = tipsFast(x at edge[,1]),
+                            internal = setdiff(getAllNodesFast(x at edge, isRooted(x)), tipsFast(x at edge[,1])),
+                            root = if (!isRooted(x)) NA else unname(E[E[, 1] == 0, 2]))
+              nid
+          })
+
 setMethod("nodeDepth", signature(x="phylo4"),
   function(x, node) {
     if (!hasEdgeLength(x))
@@ -275,6 +362,92 @@
 ### Label accessors
 #########################################################
 
+#' Labels for phylo4/phylo4d objects
+#' 
+#' Methods for creating, accessing and updating labels in phylo4/phylo4d
+#' objects
+#' 
+#' 
+#' In phylo4/phylo4d objects, tips must have labels (that's why there is no
+#' method for hasTipLabels), internal nodes and edges can have labels.
+#' 
+#' Labels must be provided as a vector of class \code{character}. The length of
+#' the vector must match the number of elements they label.
+#' 
+#' The option \code{use.names} allows the user to match a label to a particular
+#' node. In this case, the vector must have names that match the node numbers.
+#' 
+#' The function \code{labels} is mostly intended to be used internally.
+#' 
+#' @name phylo4-labels
+#' @aliases labels<- labels,phylo4-method
+#' labels<-,phylo4,ANY,ANY,character-method
+#' labels<-,phylo4d,ANY,ANY,character-method hasDuplicatedLabels
+#' hasDuplicatedLabels-methods hasDuplicatedLabels,phylo4-method hasNodeLabels
+#' hasNodeLabels-methods hasNodeLabels,phylo4-method nodeLabels
+#' nodeLabels-methods nodeLabels,phylo4-method nodeLabels<-
+#' nodeLabels<-,phylo4,character-method nodeLabels<-,phylo4d,ANY-method
+#' tipLabels tipLabels-methods tipLabels,phylo4-method tipLabels<-
+#' tipLabels<-,phylo4,character-method tipLabels<-,phylo4d,character-method
+#' hasEdgeLabels hasEdgeLabels-methods hasEdgeLabels,phylo4-method edgeLabels
+#' edgeLabels<- edgeLabels-methods edgeLabels,phylo4-method
+#' edgeLabels<-,phylo4,character-method
+#' @docType methods
+#' @param x a phylo4 or phylo4d object.
+#' @param object a phylo4 or phylo4d object.
+#' @param type which type of labels: \code{all} (tips and internal nodes),
+#' \code{tip} (tips only), \code{internal} (internal nodes only).
+#' @param value a vector of class \code{character}, see Details for more
+#' information.
+#' @param use.names should the names of the vector used to create/update labels
+#' be used to match the labels? See Details for more information.
+#' @section Methods: \describe{ \item{labels}{\code{signature(object =
+#' "phylo4")}: tip and/or internal node labels, ordered by node ID}
+#' 
+#' \item{hasDuplicatedLabels}{\code{signature(object = "phylo4")}: are any
+#' labels duplicated?}
+#' 
+#' \item{tipLabels}{\code{signature(object = "phylo4")}: tip labels, ordered by
+#' node ID}
+#' 
+#' \item{hasNodeLabels}{\code{signature(object = "phylo4")}: whether tree has
+#' (internal) node labels} \item{nodeLabels}{\code{signature(object =
+#' "phylo4")}: internal node labels, ordered by node ID}
+#' 
+#' \item{hasEdgeLabels}{\code{signature(object = "phylo4")}: whether tree has
+#' (internal) edge labels} \item{edgeLabels}{\code{signature(object =
+#' "phylo4")}: internal edge labels, ordered according to the edge matrix} }
+#' @examples
+#' 
+#' 
+#' data(geospiza)
+#' 
+#' ## Return labels from geospiza
+#' tipLabels(geospiza)
+#' 
+#' ## Internal node labels in geospiza are empty
+#' nodeLabels(geospiza)
+#' 
+#' ## Creating internal node labels
+#' ndLbl <- paste("n", 1:nNodes(geospiza), sep="")
+#' nodeLabels(geospiza) <- ndLbl
+#' nodeLabels(geospiza)
+#' 
+#' ## naming the labels
+#' names(ndLbl) <- nodeId(geospiza, "internal")
+#' 
+#' ## shuffling the labels
+#' (ndLbl <- sample(ndLbl))
+#' 
+#' ## by default, the labels are attributed in the order
+#' ## they are given:
+#' nodeLabels(geospiza) <- ndLbl
+#' nodeLabels(geospiza)
+#' 
+#' ## but use.names puts them in the correct order
+#' labels(geospiza, "internal", use.names=TRUE) <- ndLbl
+#' nodeLabels(geospiza)
+#' 
 ## return labels in increasing node order
 setMethod("labels", signature(object="phylo4"),
   function(object, type = c("all", "tip", "internal")) {
@@ -399,6 +572,57 @@
 #########################################################
 
 ### print
+
+
+#' print a phylogeny
+#' 
+#' Prints a phylo4 or phylo4d object in data.frame format with user-friendly
+#' column names
+#' 
+#' This is a user-friendly version of the tree representation, useful for
+#' checking that objects were read in completely and translated correctly. The
+#' phylogenetic tree is represented as a list of numbered nodes, linked in a
+#' particular way through time (or rates of evolutionary change).  The topology
+#' is given by the pattern of links from each node to its ancestor. Also given
+#' are the taxon names, node type (root/internal/tip) and phenotypic data (if
+#' any) associated with the node, and the branch length from the node to its
+#' ancestor. A list of nodes (descendants) and ancestors is minimally required
+#' for a phylo4 object.
+#' 
+#' @param x a \code{phylo4} tree or \code{phylo4d} tree+data object
+#' @param edgeOrder in the data frame returned, the option 'pretty' returns the
+#' internal nodes followed by the tips, the option 'real' returns the nodes in
+#' the order they are stored in the edge matrix.
+#' @param printall default prints entire tree. printall=FALSE returns the first
+#' 6 rows
+#' @return A data.frame with a row for each node (descendant), sorted as
+#' follows: root first, then other internal nodes, and finally tips.\cr The
+#' returned data.frame has the following columns:\cr \item{label}{Label for the
+#' taxon at the node (usually species name).} \item{node}{Node number, i.e. the
+#' number identifying the node in \code{x at edge}.} \item{ancestor}{Node number
+#' of the node's ancestor.} \item{branch.length}{The branch length connecting
+#' the node to its ancestor (NAs if missing).} \item{node.type}{"root",
+#' "internal", or "tip". (internally generated)} \item{data}{phenotypic data
+#' associated with the nodes, with separate columns for each variable.}
+#' @note This is the default show() method for phylo4, phylo4d. It prints the
+#' user-supplied information for building a phylo4 object. For a full
+#' description of the phylo4 S4 object and slots, see \code{\link{phylo4}}.
+#' @author Marguerite Butler Thibaut Jombart
+#' \email{jombart@@biomserv.univ-lyon1.fr} Steve Kembel
+#' @keywords methods
+#' @examples
+#' 
+#' 
+#' tree.phylo <- ape::read.tree(text="((a,b),c);")
+#' tree <- as(tree.phylo, "phylo4")
+#' ##plot(tree,show.node=TRUE) ## plotting broken with empty node labels: FIXME
+#' tip.data <- data.frame(size=c(1,2,3), row.names=c("a", "b", "c"))
+#' treedata <- phylo4d(tree, tip.data)
+#' plot(treedata)
+#' print(treedata)
+#' 
+#' 
+#' @export printphylo4
 printphylo4 <- function(x, edgeOrder=c("pretty", "real"), printall=TRUE) {
     if(!nrow(edges(x))) {
         msg <- paste("Empty \'", class(x), "\' object\n", sep="")
@@ -440,6 +664,83 @@
   })
 
 ### summary
+#' Displaying phylo4 object
+#' 
+#' Display methods for phylo4 and phylo4d phylogenetic trees
+#' 
+#' 
+#' @name phylo4-display
+#' @aliases print,phylo4-method show,phylo4-method head,phylo4-method
+#' tail,phylo4-method summary,phylo4-method names,phylo4-method
+#' @docType methods
+#' @param x a phylo4 object
+#' @param object a phylo4 object
+#' @param edgeOrder Character string indicating whether the edges should be
+#' printed as ordered in the tree "real" (e.g. preorder or postorder), or
+#' "pretty" printed with tips collated together
+#' @param printall If TRUE all tip labels are printed
+#' @param quiet a logical stating whether the results of the summary should be
+#' printed to the screen (FALSE, default) or not (TRUE)
+#' @return
+#' 
+#' The \code{summary} method invisibly returns a list with the following
+#' components:
+#' 
+#' \item{list("name")}{the name of the object} \item{list("nb.tips")}{the
+#' number of tips} \item{list("nb.nodes")}{the number of nodes}
+#' \item{list("mean.el")}{mean of edge lengths} \item{list("var.el")}{variance
+#' of edge lengths (estimate for population)} \item{list("sumry.el")}{summary
+#' (i.e. range and quartiles) of the edge lengths}
+#' \item{list("degree")}{(optional) degree (i.e. number of descendants) of each
+#' node; displayed only when there are polytomies}
+#' \item{list("polytomy")}{(optional) type of polytomy for each node:
+#' \sQuote{node}, \sQuote{terminal} (all descendants are tips) or
+#' \sQuote{internal} (at least one descendant is an internal node); displayed
+#' only when there are polytomies}
+#' 
+#' The \code{names} method returns a vector of characters corresponding to the
+#' names of the slots.
+#' @section Methods: \describe{ \item{print}{\code{signature(x = "phylo4")}:
+#' print method} \item{show}{\code{signature(object = "phylo4")}: show method }
+#' \item{summary}{\code{signature(object = "phylo4")}: summary method}
+#' \item{names}{\code{signature(x = "phylo4")}: gives the slot names}
+#' \item{head}{\code{signature(object = "phylo4")}: show first few nodes}
+#' \item{tail}{\code{signature(object = "phylo4")}: show last few nodes} }
+#' @author Ben Bolker, Thibaut Jombart
+#' @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.
+#' @keywords methods
+#' @examples
+#' 
+#' 
+#'   tOwls <- "(((Strix_aluco:4.2,Asio_otus:4.2):3.1,Athene_noctua:7.3):6.3,Tyto_alba:13.5);"
+#'   tree.owls <- ape::read.tree(text=tOwls)
+#'   P1 <- as(tree.owls, "phylo4")
+#'   P1
+#'   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,
+#'       0,  8), ncol=2, byrow=TRUE)
+#' 
+#'   P2 <- phylo4(E)
+#'   nodeLabels(P2) <- as.character(nodeId(P2, "internal"))
+#'   plot(P2, show.node.label=TRUE)
+#'   sumryP2 <- summary(P2)
+#'   sumryP2
+#' 
 setMethod("summary", signature(object="phylo4"),
   function(object, quiet=FALSE) {
 
@@ -538,6 +839,51 @@
 ### Ordering
 #########################################################
 
+#' reordering trees within phylobase objects
+#' 
+#' Methods for reordering trees into various traversal orders
+#' 
+#' The \code{reorder} method takes a \code{phylo4} or \code{phylo4d} tree and
+#' orders the edge matrix (i.e. \code{edges(x)}) in the requested traversal
+#' order. Currently only two orderings are permitted, and both require rooted
+#' trees. In "postorder", a node's descendants come before that node, thus the
+#' root, which is ancestral to all nodes, comes last.  In "preorder", a node is
+#' visited before its descendants, thus the root comes first.
+#' 
+#' A method is also defined that takes an \code{ape phylo} object.  This also
+#' takes an order argument, however, 'pruningwise' and 'cladewise' are the only
+#' acceptable parameters. This is because this method actually uses the
+#' \code{ape reorder()} command to complete the ordering.
+#' 
+#' @name reorder-methods
+#' @aliases reorder-methods reorder,phylo-method reorder,phylo4-method
+#' reorder,phylo4d-method
+#' @docType methods
+#' @param x a \code{phylo4} or \code{phylo4d} object
+#' @param order The desired traversal order; currently only 'preorder' and
+#' 'postorder' are allowed for \code{phylo4} and \code{phylo4d} objects,
+#' whereas only 'cladewise' and 'pruningwise' are allowed for \code{phylo}
+#' objects
+#' @return A \code{phylo4} or \code{phylo4d} object with the edge, label,
+#' length and data slots ordered as \code{order}, which is itself recorded in
+#' the order slot.
+#' @note The "preorder" parameter corresponds to "cladewise" in the \code{ape}
+#' package, and "postorder" corresponds (almost but close enough?) to
+#' "pruningwise".
+#' 
+#' See \url{http://ape.mpl.ird.fr/misc/FormatTreeR_28July2008.pdf}
+#' @section Methods: \describe{ \item{x = "phylo"}{reorders a \code{phylo}
+#' object} \item{x = "phylo4"}{reorders a \linkS4class{phylo4} object} \item{x
+#' = "phylo4d"}{reorders a \linkS4class{phylo4d} object} }
+#' @author Peter Cowan, Jim Regetz
+#' @seealso \code{\link[ape]{reorder.phylo}} in the \code{ape} package.
+#' \code{\link{ancestors}} \code{\link{ancestor}} \code{\link{siblings}}
+#' \code{\link{children}} \code{\link{descendants}}
+#' @keywords methods
+#' @examples
+#' phy <- phylo4(ape::rtree(5))
+#' edges(reorder(phy, "preorder"))
+#' edges(reorder(phy, "postorder"))
 orderIndex <- function(x, order=c("preorder", "postorder")) {
 
     order <- match.arg(order)

Modified: pkg/R/methods-phylo4d.R
===================================================================
--- pkg/R/methods-phylo4d.R	2014-03-17 13:15:09 UTC (rev 877)
+++ pkg/R/methods-phylo4d.R	2014-03-17 13:18:21 UTC (rev 878)
@@ -1,3 +1,56 @@
+
+#' Retrieving or updating tip and node data in phylo4d objects
+#' 
+#' Methods to retrieve or update tip, node or all data associated with a
+#' phylogenetic tree stored as a phylo4d object
+#' 
+#' 
+#' @aliases tdata tdata-method tdata,phylo4d-method tdata<-
+#' tdata<-,phylo4d-method tdata<-,phylo4d,ANY-method tipData tipData-method
+#' tipData,phylo4d-method tipData<- tipData<-,phylo4d-method
+#' tipData<-,phylo4d,ANY-method nodeData nodeData-method
+#' nodeData,phylo4d-method nodeData<- nodeData<-,phylo4d-method
+#' nodeData<-,phylo4d,ANY-method
+#' @param x A \code{phylo4d} object
+#' @param type The type of data to retrieve or update: \dQuote{\code{all}}
+#' (default) for data associated with both tip and internal nodes,
+#' \dQuote{\code{tip}} for data associated with tips only,
+#' \dQuote{\code{internal}} for data associated with internal nodes only.
+#' @param label.type How should the tip/node labels from the tree be returned?
+#' \dQuote{\code{row.names}} returns them as row names of the data frame,
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/phylobase -r 878


More information about the Phylobase-commits mailing list