Skip to content

Commit

Permalink
Merge branch 'master' into no-phangorn
Browse files Browse the repository at this point in the history
  • Loading branch information
ms609 committed Jun 27, 2024
2 parents ffef11e + ed1423a commit 24d2eeb
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 10 deletions.
2 changes: 1 addition & 1 deletion R/cluster_stats.R
Original file line number Diff line number Diff line change
Expand Up @@ -226,7 +226,7 @@ MeanMSTEdge.dist <- function(x, cluster = 1) {
d <- as.matrix(x)
diag(d) <- NA_real_
vapply(seq_along(unique(cluster)),
function(i) .MeanNN.dist(d[cluster == i, cluster == i, drop = FALSE]),
function(i) .MeanMSTEdge.dist(d[cluster == i, cluster == i, drop = FALSE]),
numeric(1))
}

Expand Down
2 changes: 1 addition & 1 deletion R/tree_distance_kendall-colijn.R
Original file line number Diff line number Diff line change
Expand Up @@ -219,7 +219,7 @@ KCDiameter.numeric <- function(tree) {

#' @export
KCDiameter.list <- function(tree) {
lapply(tree, KCDiameter)
vapply(tree, KCDiameter, double(1))
}

#' @export
Expand Down
21 changes: 13 additions & 8 deletions tests/testthat/test-information.R
Original file line number Diff line number Diff line change
Expand Up @@ -44,15 +44,20 @@ test_that("TreesConsistentWithTwoSplits works", {

Test <- function(n, a, b, score) {
logScore <- log(score)
l2Score <- log2(score)

expect_equal(score, TreesConsistentWithTwoSplits(n, a, b))
expect_equal(score, TreesConsistentWithTwoSplits(n, b, a))
expect_equal(score, TreesConsistentWithTwoSplits(n, n - a, n - b))
expect_equal(score, TreesConsistentWithTwoSplits(n, n - b, n - a))
expect_equal(logScore, LnTreesConsistentWithTwoSplits(n, a, b))
expect_equal(logScore, LnTreesConsistentWithTwoSplits(n, b, a))
expect_equal(logScore, LnTreesConsistentWithTwoSplits(n, n - a, n - b))
expect_equal(logScore, LnTreesConsistentWithTwoSplits(n, n - b, n - a))
expect_equal(TreesConsistentWithTwoSplits(n, a, b), score)
expect_equal(TreesConsistentWithTwoSplits(n, b, a), score)
expect_equal(TreesConsistentWithTwoSplits(n, n - a, n - b), score)
expect_equal(TreesConsistentWithTwoSplits(n, n - b, n - a), score)
expect_equal(Log2TreesConsistentWithTwoSplits(n, a, b), l2Score)
expect_equal(Log2TreesConsistentWithTwoSplits(n, b, a), l2Score)
expect_equal(Log2TreesConsistentWithTwoSplits(n, n - a, n - b), l2Score)
expect_equal(Log2TreesConsistentWithTwoSplits(n, n - b, n - a), l2Score)
expect_equal(LnTreesConsistentWithTwoSplits(n, a, b), logScore)
expect_equal(LnTreesConsistentWithTwoSplits(n, b, a), logScore)
expect_equal(LnTreesConsistentWithTwoSplits(n, n - a, n - b), logScore)
expect_equal(LnTreesConsistentWithTwoSplits(n, n - b, n - a), logScore)
}

Test(8, 3, 0, 315)
Expand Down
7 changes: 7 additions & 0 deletions tests/testthat/test-tree_distance_kc.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,10 @@
library("TreeTools", quietly = TRUE)

test_that("KC fails gracefully", {
expect_error(KendallColijn(BalancedTree(8), BalancedTree(1:8)),
"Leaves must bear identical labels.")
})

test_that("KC vector calculations", {

bal7 <- ape::read.tree(text = "(((t1,t2),(t3,t4)),((t5,t6),t7));")
Expand Down Expand Up @@ -45,9 +50,11 @@ test_that("KCDiameter() calculated", {
Test(4)
Test(40)
tree1 <- ape::read.tree(text = "(a, (b, (c, (d, (e, (f, (g, h)))))));")
expect_equal(KendallColijn(tree1), 0)
tree2 <- ape::read.tree(text = "(a, ((b, c), (d, (e, (f, (g, h))))));")
tree3 <- ape::read.tree(text = "(a, (b, (c, (d, (e, (f, g))))));")
trees <- c(tree1, tree2, tree3)
expect_equal(KCDiameter(trees),
c(KCDiameter(tree1), KCDiameter(tree2), KCDiameter(tree3)))
expect_equal(KCDiameter(list(tree1, tree2, tree3)), KCDiameter(trees))
})

0 comments on commit 24d2eeb

Please sign in to comment.