[Phylobase-commits] r443 - in pkg: R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Thu Jun 25 21:56:32 CEST 2009


Author: regetz
Date: 2009-06-25 21:56:31 +0200 (Thu, 25 Jun 2009)
New Revision: 443

Modified:
   pkg/R/class-phylo4.R
   pkg/R/class-phylo4d.R
   pkg/R/subset.R
   pkg/man/phylo4.Rd
Log:
created an S4 generic for phylo4, and converted the existing phylo4
function to an S4 method with signature "matrix"


Modified: pkg/R/class-phylo4.R
===================================================================
--- pkg/R/class-phylo4.R	2009-06-23 20:09:31 UTC (rev 442)
+++ pkg/R/class-phylo4.R	2009-06-25 19:56:31 UTC (rev 443)
@@ -22,12 +22,19 @@
 ## phylo4 constructor
 #####################
 
+## generic
+setGeneric("phylo4", function(x, ...) { standardGeneric("phylo4")} )
+
 # ape orderings should be allowed for so we can import trees from ape e.g. during subsetting
 phylo4_orderings <- c("unknown", "preorder", "postorder", "pruningwise", "cladewise")
 
-phylo4 <- function(edge, edge.length = NULL, tip.label = NULL, node.label = NULL, edge.label = NULL, order="unknown", ...){
+## first arg is a matrix
+setMethod("phylo4", "matrix",
+    function(x, edge.length = NULL, tip.label = NULL, node.label = NULL,
+             edge.label = NULL, order="unknown", ...) {
 
     ## edge
+    edge <- x
     mode(edge) <- "integer"
     #if(any(is.na(edge))) stop("NA are not allowed in edge matrix")
     if(ncol(edge) > 2) warning("the edge matrix has more than two columns")
@@ -121,5 +128,5 @@
     }
 
     return(res)
-}
+})
 

Modified: pkg/R/class-phylo4d.R
===================================================================
--- pkg/R/class-phylo4d.R	2009-06-23 20:09:31 UTC (rev 442)
+++ pkg/R/class-phylo4d.R	2009-06-25 19:56:31 UTC (rev 443)
@@ -118,7 +118,7 @@
 
 ## first arg is a matrix of edges
 setMethod("phylo4d", c("matrix"), function(x, tip.data=NULL, node.data=NULL, all.data=NULL, ...){
-    tree <- phylo4(edge=x,...)
+    tree <- phylo4(x, ...)
     res <- phylo4d(tree, tip.data, node.data, all.data, ...)
     return(res)
 })

Modified: pkg/R/subset.R
===================================================================
--- pkg/R/subset.R	2009-06-23 20:09:31 UTC (rev 442)
+++ pkg/R/subset.R	2009-06-25 19:56:31 UTC (rev 443)
@@ -93,7 +93,7 @@
 ## coerce phylo4d to phylo4 -- on purpose, so no warning
 
 extractTree <- function(from) {
-    phylo4(edge = from at edge, edge.length = from at edge.length,
+    phylo4(from at edge, edge.length = from at edge.length,
            tip.label = from at tip.label,
            node.label = from at node.label, edge.label = from at edge.label)
   }

Modified: pkg/man/phylo4.Rd
===================================================================
--- pkg/man/phylo4.Rd	2009-06-23 20:09:31 UTC (rev 442)
+++ pkg/man/phylo4.Rd	2009-06-25 19:56:31 UTC (rev 443)
@@ -1,14 +1,23 @@
-\name{phylo4}
+\name{phylo4-methods}
+\docType{methods}
 \alias{phylo4}
-\title{ create a phylogenetic tree object }
+\alias{phylo4-methods}
+\alias{phylo4,matrix-method}
+\title{Create a phylogenetic tree}
 \description{
-  The \code{phylo4} function 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.
+  \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.
 }
+\section{Methods}{
+  \describe{
+     \item{x = "matrix"}{creates a phylobase tree from a matrix of
+       edges}
+   }}
 \usage{
-phylo4(edge, edge.length = NULL, tip.label = NULL, node.label = NULL,
-edge.label = NULL,  order="unknown", ...)
+     \S4method{phylo4}{matrix}(x, edge.length = NULL, tip.label = NULL, node.label = NULL,
+        edge.label = NULL,  order="unknown", ...)
 }
 \arguments{
+  \item{x}{a matrix of edges}
   \item{edge}{A numeric, two-column matrix with as many rows as branches in the phylogeny.}
   \item{edge.length}{Edge (branch) length. (Optional)}
   \item{tip.label}{A character vector of species names (names of "tip" nodes). (Optional)}
@@ -18,7 +27,7 @@
       listed in \code{phylo4_ordering}, currently "unknown", "reorder"
       (="pruningwise" in \code{ape}), "postorder" (="cladewise" in
       \code{ape}))}
-    \item{\dots}{fixme?}
+  \item{\dots}{fixme?}
 }
 \details{
   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.
@@ -31,18 +40,18 @@
   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:
-mytree <- phylo4(edge=matrix(data=c(4,1, 4,5, 5,2, 5,3,NA,4), ncol=2, byrow=TRUE), tip.label=c("speciesA", "speciesB", "speciesC"))
+mytree <- phylo4(x=matrix(data=c(4,1, 4,5, 5,2, 5,3,NA,4), ncol=2, byrow=TRUE), tip.label=c("speciesA", "speciesB", "speciesC"))
 mytree
 plot(mytree)
 
 # another way to specify the same tree:
-mytree <- phylo4(edge=cbind(c(4,4,5,5,NA), c(1,5,2,3,4)), tip.label=c("speciesA", "speciesB", "speciesC"))
+mytree <- phylo4(x=cbind(c(4,4,5,5,NA), c(1,5,2,3,4)), tip.label=c("speciesA", "speciesB", "speciesC"))
 
 # another way:
-mytree <- phylo4(edge=rbind(c(4,1), c(4,5), c(5,2), c(5,3), c(NA,4)), tip.label=c("speciesA", "speciesB", "speciesC"))
+mytree <- phylo4(x=rbind(c(4,1), c(4,5), c(5,2), c(5,3), c(NA,4)), tip.label=c("speciesA", "speciesB", "speciesC"))
 
 # with branch lengths:
-mytree <- phylo4(edge=rbind(c(4,1), c(4,5), c(5,2), c(5,3), c(NA,4)),
+mytree <- phylo4(x=rbind(c(4,1), c(4,5), c(5,2), c(5,3), c(NA,4)),
 tip.label=c("speciesA", "speciesB", "speciesC"), edge.length=c(1, .2,
 .8, .8, NA))
 plot(mytree)



More information about the Phylobase-commits mailing list