diff --git a/R/class-CorrelationLink.R b/R/class-CorrelationLink.R index 5357cd2..a0f35a3 100644 --- a/R/class-CorrelationLink.R +++ b/R/class-CorrelationLink.R @@ -183,7 +183,7 @@ setClass("CorrelationLinkList", #' @param linkColorScheme Either 'none' or 'posneg'. If 'posneg', the link color will be based on the sign of the correlation coefficient. #' @param correlationCoefThreshold numeric value used to filter links based on correlationCoef. Default is NULL (i.e. no filtering). #' Any links with an absolute correlationCoef below this threshold will be removed. -#' @param pValueThreshold numeric value used to filter links based on pValue. Default is 0.05. +#' @param pValueThreshold numeric value used to filter links based on pValue. Default is NULL (i.e. no filtering). #' Any links with an pValue above this threshold will be removed. #' @return CorrelationLinkList #' @export @@ -195,7 +195,7 @@ function( object, linkColorScheme = c('none', 'posneg'), correlationCoefThreshold = NULL, - pValueThreshold = 0.05 + pValueThreshold = NULL ) standardGeneric("CorrelationLinkList"), signature = c("object")) #' @rdname CorrelationLinkList @@ -210,7 +210,7 @@ function( ), linkColorScheme = c('none', 'posneg'), correlationCoefThreshold = NULL, - pValueThreshold = 0.05 + pValueThreshold = NULL ) { linkColorScheme <- veupathUtils::matchArg(linkColorScheme) diff --git a/R/class-CorrelationNetwork.R b/R/class-CorrelationNetwork.R index cd7d28f..f1a618d 100644 --- a/R/class-CorrelationNetwork.R +++ b/R/class-CorrelationNetwork.R @@ -40,7 +40,7 @@ check_correlation_network <- function(object) { #' @slot variableMapping veupathUtils::VariableMetadataList object defining the variable mappings in the network. #' @slot correlationCoefThreshold numeric defining the correlation coefficient threshold for filtering links. Default is NA (no filtering). #' Any link with an absolute correlation coefficient below this threshold will be filtered out. -#' @slot pValueThreshold numeric defining the p-value threshold for filtering links. Default is 0.05. +#' @slot pValueThreshold numeric defining the p-value threshold for filtering links. Default is NA (no filtering). #' Any link with an p-value above this threshold will be filtered out. #' @name CorrelationNetwork-class #' @rdname CorrelationNetwork-class @@ -58,7 +58,7 @@ setClass("CorrelationNetwork", nodes = NodeList(), linkColorScheme = 'posneg', #change default from base Network's 'none' correlationCoefThreshold = NA_real_, - pValueThreshold = 0.05, + pValueThreshold = NA_real_, variableMapping = VariableMetadataList() ), validity = check_correlation_network @@ -74,7 +74,7 @@ setClass("CorrelationNetwork", #' @param object Object containing data to be converted to a Network #' @param correlationCoefThreshold numeric defining the correlation coefficient threshold for filtering links. Default is NULL (no filtering). #' Any link with an absolute correlation coefficient below this threshold will be filtered out. -#' @param pValueThreshold numeric defining the p-value threshold for filtering links. Default is 0.05. +#' @param pValueThreshold numeric defining the p-value threshold for filtering links. Default is NULL (no filtering). #' Any link with an p-value above this threshold will be filtered out. #' @param linkColorScheme string defining the type of coloring scheme the links follow. #' Options are 'none' and 'posneg' (default). @@ -93,7 +93,7 @@ setGeneric("CorrelationNetwork", links, nodes, correlationCoefThreshold = NULL, - pValueThreshold = 0.05, + pValueThreshold = NULL, linkColorScheme = 'posneg', variables = VariableMetadataList(), ... @@ -108,7 +108,7 @@ setMethod("CorrelationNetwork", signature("missing", "CorrelationLinkList", "Nod links, nodes, correlationCoefThreshold = NULL, - pValueThreshold = 0.05, + pValueThreshold = NULL, linkColorScheme = 'posneg', variables = VariableMetadataList(), pruneIsolatedNodes = c(TRUE, FALSE) @@ -139,7 +139,7 @@ setMethod("CorrelationNetwork", signature("data.frame", "missing", "missing"), f links, nodes, correlationCoefThreshold = NULL, - pValueThreshold = 0.05, + pValueThreshold = NULL, linkColorScheme = 'posneg', layout = c("nicely", "force", "circle"), variables = VariableMetadataList(), @@ -172,7 +172,7 @@ setMethod("CorrelationNetwork", signature("missing", "missing", "missing"), func links, nodes, correlationCoefThreshold = NULL, - pValueThreshold = 0.05, + pValueThreshold = NULL, linkColorScheme = 'none', variables = VariableMetadataList(), ... diff --git a/R/methods-CorrelationLinks.R b/R/methods-CorrelationLinks.R index d5165fb..57c95fd 100644 --- a/R/methods-CorrelationLinks.R +++ b/R/methods-CorrelationLinks.R @@ -29,7 +29,7 @@ setMethod("getPValues", "CorrelationLinkList", function(object) unlist(lapply(ob #' @param object CorrelationLinkList or CorrelationNetwork #' @param correlationCoefThreshold threshold to filter edges by correlation coefficient. Default is NULL. #' Any links with absolute correlation coefficients below this threshold will be removed. -#' @param pValueThreshold threshold to filter edges by p-value. Default is 0.05. +#' @param pValueThreshold threshold to filter edges by p-value. Default is NULL. #' Any links with p-values above this threshold will be removed. #' @param verbose boolean indicating if timed logging is desired #' @return CorrelationLinkList or CorrelationNetwork @@ -39,7 +39,7 @@ setGeneric("pruneCorrelationLinks", function( object, correlationCoefThreshold = NULL, - pValueThreshold = 0.05, + pValueThreshold = NULL, verbose = c(TRUE, FALSE) ) { standardGeneric("pruneCorrelationLinks") @@ -51,7 +51,7 @@ setMethod("pruneCorrelationLinks", "CorrelationLinkList", function( object, correlationCoefThreshold = NULL, - pValueThreshold = 0.05, + pValueThreshold = NULL, verbose = c(TRUE, FALSE) ) { verbose <- veupathUtils::matchArg(verbose) diff --git a/tests/testthat/test-correlation-network.R b/tests/testthat/test-correlation-network.R index 017baef..dde4b20 100644 --- a/tests/testthat/test-correlation-network.R +++ b/tests/testthat/test-correlation-network.R @@ -16,7 +16,11 @@ test_that("correlation networks can be created", { link3 <- CorrelationLink(source = nodeC, target = nodeA, correlationCoef = -.8, pValue = .1) # Create a network - net <- CorrelationNetwork(links = CorrelationLinkList(c(link1, link2, link3)), nodes = NodeList(c(nodeA, nodeB, nodeC))) + net <- CorrelationNetwork( + links = CorrelationLinkList(c(link1, link2, link3)), + nodes = NodeList(c(nodeA, nodeB, nodeC)), + pValueThreshold = .05 + ) expect_equal(getNodes(net), NodeList(c(nodeA, nodeB, nodeC))) expect_equal(getLinks(net), CorrelationLinkList(c(link1, link2))) ## link 3 is pruned for high pValue @@ -25,8 +29,7 @@ test_that("correlation networks can be created", { # Create a network net <- CorrelationNetwork( links = CorrelationLinkList(c(link1, link2, link3)), - nodes = NodeList(c(nodeA, nodeB, nodeC)), - pValueThreshold = NULL + nodes = NodeList(c(nodeA, nodeB, nodeC)) ) expect_equal(getNodes(net), NodeList(c(nodeA, nodeB, nodeC))) @@ -89,8 +92,7 @@ test_that("correlation networks can be pruned by threshold", { # Create a network net <- CorrelationNetwork( links = CorrelationLinkList(c(link1, link2, link3)), - nodes = NodeList(c(nodeA, nodeB, nodeC)), - pValueThreshold = NULL + nodes = NodeList(c(nodeA, nodeB, nodeC)) ) net <- pruneCorrelationLinks(net, pValueThreshold = .05) @@ -124,8 +126,7 @@ test_that("toJSON works for networks", { # Create a network net <- CorrelationNetwork( links = CorrelationLinkList(c(link1, link2, link3)), - nodes = NodeList(c(nodeA, nodeB, nodeC)), - pValueThreshold = NULL + nodes = NodeList(c(nodeA, nodeB, nodeC)) ) # Convert to JSON @@ -142,7 +143,8 @@ test_that("toJSON works for networks", { net <- CorrelationNetwork( links = CorrelationLinkList(c(link1, link2, link3)), - nodes = NodeList(c(nodeA, nodeB, nodeC)) + nodes = NodeList(c(nodeA, nodeB, nodeC)), + pValueThreshold = .05 ) json <- veupathUtils::toJSON(net) @@ -165,7 +167,7 @@ test_that("we can build a Network from an edgeList data.frame", { correlationCoef = c(.8,.3,-.8), pValue = c(.01,.001,.1) ) - net <- CorrelationNetwork(object = edgeList, linkColorScheme = 'none', pValueThreshold = NULL) + net <- CorrelationNetwork(object = edgeList, linkColorScheme = 'none') expect_equal(getNodeIds(net), c('a', 'b', 'c')) expect_equal(getDegrees(net), c(2, 2, 2)) expect_equal(!is.null(getCoords(net)), TRUE) @@ -181,7 +183,7 @@ test_that("we can build a Network from an edgeList data.frame", { correlationCoef = c(.8,.3,-.8), pValue = c(.01,.001,.1) ) - net <- CorrelationNetwork(object = edgeList, linkColorScheme = 'posneg', pValueThreshold = NULL) + net <- CorrelationNetwork(object = edgeList, linkColorScheme = 'posneg') expect_equal(getNodeIds(net), c('a', 'b', 'c')) expect_equal(getDegrees(net), c(2, 2, 2)) expect_equal(!is.null(getCoords(net)), TRUE) @@ -201,7 +203,7 @@ test_that("we can build a Network from an edgeList data.frame", { correlationCoef = c(.8,.3,-.8), pValue = c(.01,.001,.1) ) - net <- CorrelationNetwork(object = edgeList) + net <- CorrelationNetwork(object = edgeList, pValueThreshold = .05) expect_equal(getNodeIds(net), c('a', 'b', 'c')) expect_equal(getDegrees(net), c(2, 2, 2)) expect_equal(!is.null(getCoords(net)), TRUE) @@ -217,12 +219,12 @@ test_that("we can build a Network from an edgeList data.frame", { correlationCoef = c(.8,.3,-.8), pValue = c(.01,.001,.1) ) - net <- CorrelationNetwork(object = edgeList, correlationCoefThreshold = .5, pValueThreshold = NULL) + net <- CorrelationNetwork(object = edgeList, correlationCoefThreshold = .5) expect_equal(getNodeIds(net), c('a', 'b', 'c')) expect_equal(getDegrees(net), c(2, 2, 2)) expect_equal(!is.null(getCoords(net)), TRUE) expect_equal(getLinkColorScheme(net), 'posneg') expect_equal(length(getLinks(net)), 2) expect_equal(getLinks(net)[[1]]@weight, .8) - expect_equal(getLinks(net)[[2]]@weight, .8) #second link is actually third link!! + expect_equal(getLinks(net)[[2]]@weight, .8) #second link is actually third link bc of correlationCoefThreshold!! }) \ No newline at end of file