Skip to content

Commit

Permalink
Merge pull request #243 from VEuPathDB/network-tests
Browse files Browse the repository at this point in the history
Network tests
  • Loading branch information
d-callan authored Feb 15, 2024
2 parents 1ac962c + 4cdbac9 commit ca188e4
Show file tree
Hide file tree
Showing 4 changed files with 162 additions and 8 deletions.
2 changes: 1 addition & 1 deletion R/class-Node.R
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ setClass("NodeId",
check_node_id_list <- function(object) {
errors <- character()

# make sure all ids are unique
# make sure all ids are unique
if (length(unique(unlist(lapply(object, id)))) != length(unlist(lapply(object, id)))) {
errors <- c(errors, "Node ids must be unique")
}
Expand Down
23 changes: 23 additions & 0 deletions tests/testthat/test-kpartite-network.R
Original file line number Diff line number Diff line change
Expand Up @@ -94,6 +94,29 @@ test_that("k-partite networks cannot be created from nonsensical inputs", {
))
})

test_that("partitions related methods work", {
edgeList <- data.frame(
source = c('a', 'b', 'c'),
target = c('b', 'a', 'd')
)

partitions = Partitions(list(
Partition(list(Node('a'), Node('c'))),
Partition(list(Node('b'), Node('d')))
))

net <- KPartiteNetwork(
object = edgeList,
partitions = partitions
)

# test getAllNodeIds
expect_equal(getAllNodeIds(partitions), c('a', 'c', 'b', 'd')) # should this be a NodeIdList?

# test partitions
expect_equal(partitions(net), Partitions(list(Partition(list(Node('a'), Node('c'))), Partition(list(Node('b'), Node('d'))))))
})

test_that("toJSON works for k-partite networks", {
# Create some nodes
nodeA <- Node(
Expand Down
83 changes: 82 additions & 1 deletion tests/testthat/test-links.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,53 @@ test_that("Links work", {
nodeB <- Node(
id = NodeId('B')
)

link <- Link(source = nodeA, target = nodeB)
expect_equal(class(link)[1], 'Link')
expect_equal(source(link), nodeA)
expect_equal(target(link), nodeB)
expect_equal(weight(link), 1)
expect_true(is.null(color(link)))

# Make another link w colors and weights
link <- Link(source = nodeA, target = nodeB, color = 'red', weight = 10)
expect_equal(class(link)[1], 'Link')
expect_equal(source(link), nodeA)
expect_equal(target(link), nodeB)
expect_equal(color(link), 'red')
expect_equal(weight(link), 10)

# pass characters for node ids
link <- Link(source = 'A', target = 'B')
expect_equal(class(link)[1], 'Link')
expect_equal(source(link), nodeA)
expect_equal(target(link), nodeB)
expect_equal(weight(link), 1)
expect_true(is.null(color(link)))

# pass numbers for node ids
link <- Link(source = 1, target = 2)
expect_equal(class(link)[1], 'Link')
expect_equal(source(link), Node(1))
expect_equal(target(link), Node(2))
expect_equal(weight(link), 1)
expect_true(is.null(color(link)))

# pass NodeId objects for node ids
link <- Link(source = NodeId('A'), target = NodeId('B'))
expect_equal(class(link)[1], 'Link')
expect_equal(source(link), nodeA)
expect_equal(target(link), nodeB)
expect_equal(weight(link), 1)
expect_true(is.null(color(link)))

# an empty one
link <- Link()
expect_equal(class(link)[1], 'Link')
expect_equal(class(source(link))[1], 'Node')
expect_equal(class(target(link))[1], 'Node')
expect_equal(weight(link), 1)
expect_true(is.null(color(link)))
})

test_that("Link methods work", {
Expand All @@ -24,12 +69,14 @@ test_that("Link methods work", {
expect_equal(target(link), nodeB)
expect_equal(weight(link), 1)
expect_true(is.null(color(link)))
expect_equal(isDirected(link), FALSE)

link <- Link(source = nodeA, target = nodeB, color = 'red', weight = 10)
expect_equal(source(link), nodeA)
expect_equal(target(link), nodeB)
expect_equal(color(link), 'red')
expect_equal(weight(link), 10)
expect_equal(isDirected(link), FALSE)

})

Expand Down Expand Up @@ -59,7 +106,7 @@ test_that("LinkList methods work", {
expect_equal(getColors(linkList), c(NULL, NULL, NULL))


# Create some more links
# Create some more links with colors and weights
link1 <- Link(source = nodeA, target = nodeB, weight = 2, color = 'red')
link2 <- Link(source = nodeB, target = nodeC, weight = 0.1, color = 'blue')
link3 <- Link(source = nodeC, target = nodeA, weight = 3, color = 'green')
Expand All @@ -70,6 +117,19 @@ test_that("LinkList methods work", {
expect_equal(getTargetNodes(linkList), list(nodeB, nodeC, nodeA))
expect_equal(getWeights(linkList), c(2, 0.1, 3))
expect_equal(getColors(linkList), c('red', 'blue', 'green'))

# use a list to make LinkList
linkList <- LinkList(list(link1, link2, link3))
expect_equal(length(linkList), 3)
expect_equal(getSourceNodes(linkList), list(nodeA, nodeB, nodeC))
expect_equal(getTargetNodes(linkList), list(nodeB, nodeC, nodeA))
expect_equal(getWeights(linkList), c(2, 0.1, 3))
expect_equal(getColors(linkList), c('red', 'blue', 'green'))

# use an edgeList to make LinkList
edgeList <- data.frame(source = 'A', target = 'B')
expect_equal(class(LinkList(edgeList))[1], 'LinkList')
expect_equal(length(LinkList(edgeList)), 1)
})

test_that("Links cannot be created from nonsensical inputs", {
Expand All @@ -82,6 +142,9 @@ test_that("Links cannot be created from nonsensical inputs", {
id = NodeId('B')
)

# self links should fail
expect_error(Link(source = nodeA, target = nodeA))
# color should be a string or number or NULL
expect_error(Link(source = nodeA, target = nodeB, color = false, weight = 10))
})

Expand Down Expand Up @@ -114,3 +177,21 @@ test_that("LinkLists cannot be created from nonsensical inputs", {
weight(link3) <- 100
expect_error(LinkList(S4Vectors::SimpleList(c(link1, link2, link3))))
})

test_that("toJSON methods for links work", {
nodeA <- Node('A')
nodeB <- Node('B')
link <- Link(source = nodeA, target = nodeB)
expect_equal(veupathUtils::toJSON(link), '{"source":"A","target":"B","weight":1,"isDirected":false}')
expect_equal(veupathUtils::toJSON(link, named = TRUE), '{"link":{"source":"A","target":"B","weight":1,"isDirected":false}}')

# w colors and weights
link <- Link(source = nodeA, target = nodeB, color = 'red', weight = 10)
expect_equal(veupathUtils::toJSON(link), '{"source":"A","target":"B","weight":10,"color":"red","isDirected":false}')
expect_equal(veupathUtils::toJSON(link, named = TRUE), '{"link":{"source":"A","target":"B","weight":10,"color":"red","isDirected":false}}')

# LinkList
linkList <- LinkList(list(link))
expect_equal(veupathUtils::toJSON(linkList), '{"links":[{"source":"A","target":"B","weight":10,"color":"red","isDirected":false}]}')
expect_equal(veupathUtils::toJSON(linkList, named = FALSE), '[{"source":"A","target":"B","weight":10,"color":"red","isDirected":false}]')
})
62 changes: 56 additions & 6 deletions tests/testthat/test-nodes.R
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,11 @@ test_that("NodeIdList works", {
expect_equal(class(NodeIdList(list(Node(id=NodeId('A')))))[1], 'NodeIdList')
expect_equal(class(NodeIdList(Node(id=NodeId('A'))))[1], 'NodeIdList')
expect_equal(class(NodeIdList(list(Node(id=NodeId('A')), Node(id=NodeId('B')))))[1], 'NodeIdList')
expect_equal(class(NodeIdList(c('A', 'B')))[1], 'NodeIdList')
expect_equal(class(NodeIdList())[1], 'NodeIdList')

edgeList <- data.frame(source = 'A', target = 'B')
expect_equal(class(NodeIdList(edgeList))[1], 'NodeIdList')

expect_error(NodeIdList(S4Vectors::SimpleList(c(NodeId('A'), 'B'))))
expect_error(NodeIdList(S4Vectors::SimpleList(c('A', 'B'))))
Expand All @@ -19,19 +24,27 @@ test_that("Node methods work", {
nodeA <- Node(
id = NodeId('A')
)

expect_equal(class(nodeA)[1], 'Node')
expect_equal(id(nodeA), 'A')
expect_equal(color(nodeA), NULL)
expect_equal(weight(nodeA), NULL)

nodeB <- Node(
id = NodeId('B'),
color = 'red',
weight = 10
)
# use a different constructor method
nodeB <- Node('B', color = 'red', weight = 10)

expect_equal(class(nodeB)[1], 'Node')
expect_equal(id(nodeB), 'B')
expect_equal(color(nodeB), 'red')
expect_equal(weight(nodeB), 10)

# numeric id
nodeC <- Node(1, color = 'red', weight = 10)

expect_equal(class(nodeC)[1], 'Node')
expect_equal(id(nodeC), "1")
expect_equal(color(nodeC), 'red')
expect_equal(weight(nodeC), 10)
})

test_that("NodeList methods work", {
Expand Down Expand Up @@ -77,7 +90,22 @@ test_that("NodeList methods work", {
expect_equal(getWeights(nodeList), c(10, 20, 30))
expect_equal(getColors(nodeList), c('red', 'blue', 'green'))

# use a different constructor method
nodeList <- NodeList(c(nodeA, nodeB, nodeC))
expect_equal(length(nodeList), 3)
expect_equal(getNodeIds(nodeList), c('A', 'B', 'C'))
expect_equal(getWeights(nodeList), c(10, 20, 30))
expect_equal(getColors(nodeList), c('red', 'blue', 'green'))

# use a different constructor method
nodeList <- NodeList(list(nodeA, nodeB, nodeC))
expect_equal(length(nodeList), 3)
expect_equal(getNodeIds(nodeList), c('A', 'B', 'C'))
expect_equal(getWeights(nodeList), c(10, 20, 30))
expect_equal(getColors(nodeList), c('red', 'blue', 'green'))

edgeList <- data.frame(source = 'A', target = 'B')
expect_equal(class(NodeList(edgeList))[1], 'NodeList')

})

Expand All @@ -91,7 +119,7 @@ test_that("We cannot make nonsensical nodes", {

test_that("We cannot make nonsensical NodeLists", {

# Create some nodes
# Create some nodes
nodeA <- Node(
id = NodeId('A')
)
Expand All @@ -111,3 +139,25 @@ test_that("We cannot make nonsensical NodeLists", {
weight(nodeA) <- 100
expect_error(NodeList(S4Vectors::SimpleList(c(nodeA, nodeB))))
})

test_that("toJSON methods for nodes work", {
nodeA <- Node('A')
expect_equal(veupathUtils::toJSON(nodeA), '{"id":"A"}')
expect_equal(veupathUtils::toJSON(nodeA, named = TRUE), '{"node":{"id":"A"}}')

# w weights and colors
nodeB <- Node('B', color = 'red', weight = 10)
expect_equal(veupathUtils::toJSON(nodeB), '{"id":"B","color":"red","weight":10}')
expect_equal(veupathUtils::toJSON(nodeB, named = TRUE), '{"node":{"id":"B","color":"red","weight":10}}')

#NodeList
nodeA <- Node('A', color='blue', weight=5)
nodeList <- NodeList(list(nodeA, nodeB))
expect_equal(veupathUtils::toJSON(nodeList), '{"nodes":[{"id":"A","color":"blue","weight":5},{"id":"B","color":"red","weight":10}]}')
expect_equal(veupathUtils::toJSON(nodeList, named = FALSE), '[{"id":"A","color":"blue","weight":5},{"id":"B","color":"red","weight":10}]')

#NodeIdList
nodeIdList <- NodeIdList(list(NodeId('A'), NodeId('B')))
expect_equal(veupathUtils::toJSON(nodeIdList), '{"nodeIds":["A","B"]}')
expect_equal(veupathUtils::toJSON(nodeIdList, named = FALSE), '["A","B"]')
})

0 comments on commit ca188e4

Please sign in to comment.