]> git.donarmstrong.com Git - ape.git/commitdiff
fix in c.multiPhylo()
authorparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Thu, 4 Aug 2011 11:00:29 +0000 (11:00 +0000)
committerparadis <paradis@6e262413-ae40-0410-9e79-b911bd7a66b7>
Thu, 4 Aug 2011 11:00:29 +0000 (11:00 +0000)
git-svn-id: https://svn.mpl.ird.fr/ape/dev/ape@167 6e262413-ae40-0410-9e79-b911bd7a66b7

NEWS
R/DNA.R
R/compute.brtime.R
R/summary.phylo.R

diff --git a/NEWS b/NEWS
index 92a114a894985d76db2d846577d8da3ff8d04ef1..0fb711979f9b827a89a072ca869d5606a6b1e201 100644 (file)
--- a/NEWS
+++ b/NEWS
@@ -31,6 +31,8 @@ BUG FIXES
       incompatible splits occur in 50% of the trees (especially with
       small number of trees).
 
+    o c() with "multiPhylo" did not work correctly.
+
 
 
                CHANGES IN APE VERSION 2.7-2
diff --git a/R/DNA.R b/R/DNA.R
index 63306ef9cc78e3c2556c8196f71520e931ca625e..df5b892192977628392406ecf0b52bd9a91ba1cf 100644 (file)
--- a/R/DNA.R
+++ b/R/DNA.R
@@ -359,7 +359,7 @@ dist.dna <- function(x, model = "K80", variance = FALSE, gamma = FALSE,
         stop(paste("'model' must be one of:",
                    paste("\"", MODELS, "\"", sep = "", collapse = " ")))
     if (imod == 11 && variance) {
-        warning("computing variance temporarily not available for model BH87.")
+        warning("computing variance not available for model BH87.")
         variance <- FALSE
     }
     if (gamma && imod %in% c(1, 5:7, 9:15)) {
index 727fcb6a37dc9fb261f8e4187d3f3d441a7293ed..822f6f2732f88806c2a071e913f69b06db1df682 100644 (file)
@@ -1,4 +1,4 @@
-## compute.brtime.R (2011-07-15)
+## compute.brtime.R (2011-07-26)
 
 ##   Compute and Set Branching Times
 
@@ -19,9 +19,9 @@ compute.brtime <-
     ## x: branching times (aka, node ages or heights)
 
     if (identical(method, "coalescent")) { # the default
-        x <- 2 * rexp(n - 1)/(as.double(n:2) * as.double((n - 1):1))
-        if (is.null(force.positive))
-            force.positive <- TRUE
+        x <- 2 * rexp(m)/(as.double((m + 1):2) * as.double(m:1))
+        ## x <- 2 * rexp(n - 1)/(as.double(n:2) * as.double((n - 1):1))
+        if (is.null(force.positive)) force.positive <- TRUE
     } else if (is.numeric(method)) {
         x <- as.vector(method)
         if (length(x) != m)
index e44d48decf6883f76adc294617bce092365599d8..715021b4db094de084235b07082621e69dd9009b 100644 (file)
@@ -1,8 +1,8 @@
-## summary.phylo.R (2010-11-03)
+## summary.phylo.R (2011-08-04)
 
 ##   Print Summary of a Phylogeny and "multiPhylo" operators
 
-## Copyright 2003-2010 Emmanuel Paradis, and 2006 Ben Bolker
+## Copyright 2003-2011 Emmanuel Paradis, and 2006 Ben Bolker
 
 ## This file is part of the R-package `ape'.
 ## See the file ../COPYING for licensing issues.
@@ -70,18 +70,6 @@ summary.phylo <- function(object, ...)
 
         }
     }
-    if (!is.null(attr(object, "loglik"))) {
-        cat("Phylogeny estimated by maximum likelihood.\n")
-        cat("  log-likelihood:", attr(object, "loglik"), "\n\n")
-        npart <- length(attr(object, "para"))
-        for (i in 1:npart) {
-            cat("partition ", i, ":\n", sep = "")
-            print(attr(object, "para")[[i]])
-            if (i == 1) next
-            else cat("  contrast parameter (xi):",
-                     attr(object, "xi")[i - 1], "\n")
-        }
-    }
 }
 
 ### by BB:
@@ -100,7 +88,7 @@ print.phylo <- function(x, printlen = 6,...)
         cat("\tNode labels:\n")
         if (nb.node > printlen) {
             cat(paste("\t", paste(x$node.label[1:printlen],
-                                 collapse=", "), ",...\n", sep = ""))
+                                 collapse=", "), ", ...\n", sep = ""))
         } else print(x$node.label)
     }
     rlab <- if (is.rooted(x)) "Rooted" else "Unrooted"
@@ -157,8 +145,8 @@ c.multiPhylo <- function(..., recursive = FALSE)
     n <- length(obj)
     x <- obj[[1L]]
     N <- length(x)
-    i <- 1L
-    while (i < n) {
+    i <- 2L
+    while (i <= n) {
         a <- N + 1L
         N <- N + length(obj[[i]])
         ## x is of class "multiPhylo", so this uses the operator below: