Skip to content

Commit

Permalink
Merge pull request #256 from VEuPathDB/correlation-networks
Browse files Browse the repository at this point in the history
Correlation networks
  • Loading branch information
d-callan authored Apr 26, 2024
2 parents f89721a + 366dc34 commit 6df5b39
Show file tree
Hide file tree
Showing 24 changed files with 1,222 additions and 61 deletions.
4 changes: 4 additions & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,9 @@ Collate:
'class-Node.R'
'constructors-Node.R'
'class-Link.R'
'class-CorrelationLink.R'
'class-Network.R'
'class-CorrelationNetwork.R'
'methods-Links.R'
'methods-Nodes.R'
'class-Partitions.R'
Expand All @@ -64,6 +66,8 @@ Collate:
'class-plotdata.R'
'group.R'
'methods-ContingencyTable.R'
'methods-CorrelationLinks.R'
'methods-CorrelationNetwork.R'
'methods-KPartiteNetwork.R'
'methods-Network.R'
'panel.R'
Expand Down
10 changes: 9 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,9 @@ S3method(numBinsToBinWidth,Date)
S3method(numBinsToBinWidth,default)
export("%>%")
export(ContingencyTable)
export(CorrelationLink)
export(CorrelationLinkList)
export(CorrelationNetwork)
export(KPartiteNetwork)
export(Link)
export(LinkList)
Expand Down Expand Up @@ -63,10 +66,13 @@ export(orderByReferenceValues)
export(outliers)
export(posPredictiveValue)
export(prevalence)
export(pruneCorrelationLinks)
export(pruneDuplicateLinks)
export(pruneIsolatedNodes)
export(pruneLinksAboveWeight)
export(pruneLinksBelowWeight)
export(pruneLinksByCorrelationCoef)
export(pruneLinksByPValue)
export(pruneLinksByPredicate)
export(relativeRisk)
export(scattergl)
Expand All @@ -77,6 +83,9 @@ export(specificity)
export(writeJSON)
export(writeNetworkJSON)
exportClasses(ContingencyTable)
exportClasses(CorrelationLink)
exportClasses(CorrelationLinkList)
exportClasses(CorrelationNetwork)
exportClasses(Link)
exportClasses(LinkList)
exportClasses(Network)
Expand Down Expand Up @@ -111,7 +120,6 @@ exportMethods(relativeRisk)
exportMethods(sensitivity)
exportMethods(specificity)
exportMethods(toJSON)
exportMethods(writeNetworkJSON)
import(data.table)
import(veupathUtils)
importFrom(S4Vectors,SimpleList)
Expand Down
284 changes: 284 additions & 0 deletions R/class-CorrelationLink.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,284 @@


check_correlation_link <- function(object) {

errors <- character()

# check correlation coef (weight) and pvalue make some sense
if (object@correlationCoef < -1 || object@correlationCoef > 1) {
msg <- "Correlation coefficient must be between -1 and 1."
errors <- c(errors, msg)
}

if (object@pValue < 0 || object@pValue > 1) {
msg <- "P-value must be between 0 and 1."
errors <- c(errors, msg)
}

# check that weight is the abs value of the correlation coefficient
if (abs(object@correlationCoef) != object@weight) {
msg <- "Weight must be the absolute value of the correlation coefficient."
errors <- c(errors, msg)
}

return(if (length(errors) == 0) TRUE else errors)
}

#' CorrelationLink
#'
#' Represent one singular link in a correlation network. A link has a source,
#' a target, a correlation coefficient, and a p-value. Its weight is the
#' absolute value of the correlation coefficient. It is undirected.
#' It may have a color, timestamp, or label (coming soon!)
#'
#' @name CorrelationLink-class
#' @rdname CorrelationLink-class
#' @include class-Node.R
#' @include constructors-Node.R
#' @include class-Link.R
#' @export
setClass("CorrelationLink",
contains = "Link",
slots = list(
correlationCoef = "numeric",
pValue = "numeric"
),
prototype = prototype(
source = NodeId(),
target = NodeId(),
color = NULL,
isDirected = FALSE,
correlationCoef = NA_real_,
pValue = NA_real_,
weight = NA_real_ # change default of 1 from parent Link class
),
validity = check_correlation_link
)

#' CorrelationLink constructor
#'
#' @param source The source node identifier
#' @param target The target node identifier
#' @param correlationCoef The correlation coefficient (weight) of the link
#' @param pValue The p-value of the link
#' @param color The color of the link
#' @export
#' @rdname CorrelationLink
setGeneric("CorrelationLink",
function(
source,
target,
correlationCoef = 1,
pValue = NULL,
color = NULL
) standardGeneric("CorrelationLink"),
signature = c("source", "target"))

#' @rdname CorrelationLink
#' @aliases CorrelationLink,Node,Node-method
setMethod("CorrelationLink", c("Node", "Node"), function(source, target, correlationCoef, pValue, color = NULL) {
new("CorrelationLink",
source = NodeId(id(source)),
target = NodeId(id(target)),
correlationCoef = correlationCoef,
pValue = pValue,
color = color,
weight = abs(correlationCoef)
)
})

#' @rdname CorrelationLink
#' @aliases CorrelationLink,character,character-method
setMethod("CorrelationLink", c("character", "character"), function(source, target, correlationCoef, pValue, color = NULL) {
CorrelationLink(
source = NodeId(source),
target = NodeId(target),
correlationCoef = correlationCoef,
pValue = pValue,
color = color
)
})

#' @rdname CorrelationLink
#' @aliases CorrelationLink,numeric,numeric-method
setMethod("CorrelationLink", c("numeric", "numeric"), function(source, target, correlationCoef, pValue, color = NULL) {
CorrelationLink(
source = NodeId(source),
target = NodeId(target),
correlationCoef = correlationCoef,
pValue = pValue,
color = color
)
})

#' @rdname CorrelationLink
#' @aliases CorrelationLink,NodeId,NodeId-method
setMethod("CorrelationLink", c("NodeId", "NodeId"), function(source, target, correlationCoef, pValue, color = NULL) {
new("CorrelationLink",
source = source,
target = target,
correlationCoef = correlationCoef,
pValue = pValue,
color = color,
weight = abs(correlationCoef)
)
})

#' @rdname CorrelationLink
#' @aliases CorrelationLink,missing,missing-method
setMethod("CorrelationLink", c("missing", "missing"), function(source, target, correlationCoef, pValue, color = NULL) {
new("CorrelationLink")
})

check_correlation_link_list <- function(object) {

errors <- character()
trueOrPrevErrors <- check_link_list(object)
if (inherits(trueOrPrevErrors, "character")) {
errors <- c(errors, trueOrPrevErrors)
}

# If one link has a correlationCoef, all must have a correlationCoef
if (any(unlist(lapply(object, function(x) {!is.null(correlationCoef(x))})))) {
if (!all(unlist(lapply(object, function(x) {!is.null(correlationCoef(x))})))) {
errors <- c(errors, "If one link has a correlationCoef, all links must have a correlationCoef.")
}
}

# If one link has a pValue, all must have a pValue
if (any(unlist(lapply(object, function(x) {!is.null(pValue(x))})))) {
if (!all(unlist(lapply(object, function(x) {!is.null(pValue(x))})))) {
errors <- c(errors, "If one link has a pValue, all links must have a pValue.")
}
}

return(if (length(errors) == 0) TRUE else errors)

}

#' Correlation Link List
#'
#' A class for representing links in a correlation network
#'
#' @name CorrelationLinkList-class
#' @rdname CorrelationLinkList-class
#' @importFrom S4Vectors SimpleList
#' @export
setClass("CorrelationLinkList",
contains = "SimpleList",
prototype = prototype(
elementType = "CorrelationLink"
),
validity = check_correlation_link_list
)

#' Generate a CorrelationLinkList
#'
#' Generate a CorrelationLinkList from an edgeList
#' @param object Object containing data to be converted to a LinkList. Could be a SimpleList of Links or a data.frame
#' with columns source, target, correlationCoef, pValue.
#' @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 NULL (i.e. no filtering).
#' Any links with an pValue above this threshold will be removed.
#' @return CorrelationLinkList
#' @export
#' @examples
#' CorrelationLinkList(data.frame(source='a',target='b',correlationCoef=0.5,pValue=0.01))
#' @rdname CorrelationLinkList
setGeneric("CorrelationLinkList",
function(
object,
linkColorScheme = c('none', 'posneg'),
correlationCoefThreshold = NULL,
pValueThreshold = NULL
) standardGeneric("CorrelationLinkList"), signature = c("object"))

#' @rdname CorrelationLinkList
#' @aliases CorrelationLinkList,data.frame-method
setMethod("CorrelationLinkList", "data.frame",
function(
object = data.frame(
source=character(),
target=character(),
correlationCoef=numeric(),
pValue=numeric()
),
linkColorScheme = c('none', 'posneg'),
correlationCoefThreshold = NULL,
pValueThreshold = NULL
) {
linkColorScheme <- veupathUtils::matchArg(linkColorScheme)

if (!inherits(isValidEdgeList(object), "logical")) {
stop(paste("Invalid edgeList:", isValidEdgeList(object), collapse = '\n'))
}

## additional validation of correlationCoef and pValue in edgeList
if (!all(c('correlationCoef', 'pValue') %in% colnames(object))) {
stop("edgeList must contain columns 'correlationCoef' and 'pValue' for CorrelationLinkList/ CorrelationNetwork")
}

## remove rows w NA correlationCoef, or not meeting thresholds
object <- object[!is.na(object$correlationCoef), ]

if (!is.null(correlationCoefThreshold)) {
object <- object[abs(object$correlationCoef) >= correlationCoefThreshold, ]
}
if (!is.null(pValueThreshold)) {
object <- object[object$pValue <= pValueThreshold, ]
}

if (nrow(object) == 0) {
new("CorrelationLinkList")
}

makeLink <- function(rowInEdgeList, linkColorScheme) {
source <- unname(rowInEdgeList['source'])
target <- unname(rowInEdgeList['target'])
correlationCoef <- as.numeric(unname(rowInEdgeList['correlationCoef']))
pValue <- as.numeric(unname(rowInEdgeList['pValue']))

if (linkColorScheme == 'posneg') {
if (correlationCoef < 0) {
color <- -1
} else if (correlationCoef > 0) {
color <- 1
} else {
color <- 0
}
} else {
color <- NA_character_
}

if (is.na(color)) {
link <- CorrelationLink(source, target, correlationCoef, pValue, NULL)
} else {
link <- CorrelationLink(source, target, correlationCoef, pValue, color)
}

return(link)
}

linkList <- apply(object, 1, makeLink, linkColorScheme)
new("CorrelationLinkList", linkList)
})

#' @rdname CorrelationLinkList
#' @aliases CorrelationLinkList,missing-method
setMethod("CorrelationLinkList", "missing", function(object) {
new("CorrelationLinkList")
})

#' @rdname CorrelationLinkList
#' @aliases CorrelationLinkList,SimpleList-method
setMethod("CorrelationLinkList", "SimpleList", function(object) {
new("CorrelationLinkList", object)
})

#' @rdname CorrelationLinkList
#' @aliases CorrelationLinkList,list-method
setMethod("CorrelationLinkList", "list", function(object) {
new("CorrelationLinkList", object)
})
Loading

0 comments on commit 6df5b39

Please sign in to comment.