Skip to content

Commit

Permalink
AddMapping and related checks
Browse files Browse the repository at this point in the history
- AddMapping accepts a list obj
- checkMapping checks if mapping obj is a list, if entries are strings, and for overlapping features across models
- validateMapping checks whether results features match with features present in mapping object and model names match model names from results table
  • Loading branch information
curadomr committed Nov 4, 2021
1 parent ca1cbf1 commit ec12603
Show file tree
Hide file tree
Showing 16 changed files with 299 additions and 6 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ export(addBarcodes)
export(addEnrichments)
export(addEnrichmentsLinkouts)
export(addFeatures)
export(addMapping)
export(addMetaFeatures)
export(addMetaFeaturesLinkouts)
export(addModels)
Expand All @@ -37,6 +38,7 @@ export(getFavicons)
export(getFeatures)
export(getInstalledStudies)
export(getLinkFeatures)
export(getMapping)
export(getMetaFeatures)
export(getMetaFeaturesLinkouts)
export(getMetaFeaturesTable)
Expand Down
37 changes: 35 additions & 2 deletions R/add.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@
#' @inheritParams addEnrichments
#' @inheritParams addMetaFeatures
#' @inheritParams addPlots
#' @inheritParams addMapping
#' @inheritParams addBarcodes
#' @inheritParams addReports
#' @inheritParams addResultsLinkouts
Expand All @@ -51,6 +52,7 @@
#' \code{\link{addEnrichments}},
#' \code{\link{addMetaFeatures}},
#' \code{\link{addPlots}},
#' \code{\link{addMapping}},
#' \code{\link{addBarcodes}},
#' \code{\link{addReports}},
#' \code{\link{addResultsLinkouts}},
Expand Down Expand Up @@ -86,6 +88,7 @@ createStudy <- function(name,
enrichments = list(),
metaFeatures = list(),
plots = list(),
mapping = list(),
barcodes = list(),
reports = list(),
resultsLinkouts = list(),
Expand Down Expand Up @@ -115,6 +118,7 @@ createStudy <- function(name,
enrichments = list(),
metaFeatures = list(),
plots = list(),
mapping = list(),
barcodes = list(),
reports = list(),
resultsLinkouts = list(),
Expand All @@ -137,6 +141,7 @@ createStudy <- function(name,
study <- addEnrichments(study, enrichments = enrichments)
study <- addMetaFeatures(study, metaFeatures = metaFeatures)
study <- addPlots(study, plots = plots)
study <- addMapping(study, mapping = mapping)
study <- addBarcodes(study, barcodes = barcodes)
study <- addReports(study, reports = reports)
study <- addResultsLinkouts(study, resultsLinkouts = resultsLinkouts)
Expand Down Expand Up @@ -387,8 +392,8 @@ addMetaFeatures <- function(study, metaFeatures, reset = FALSE) {
#' required metadata element is \code{displayName}, which controls how the
#' plot will be named in the app. You are encouraged to also specify the
#' \code{plotType}, e.g. \code{"singleFeature"}, \code{"multiFeature"},
#' \code{"multiTest"}. Note that PlotType accepts a vector of entries,
#' whenever applicable, e.g., plotType = c(\code{"multiFeature"},
#' \code{"multiTest"}, \code{"multiModel"}. PlotType accepts vector of
#' entries, whenever applicable, e.g., plotType = c(\code{"multiFeature"},
#' \code{"multiTest"}). If you do not specify the \code{plotType}, the plot
#' will be assumed to be \code{"singleFeature"} and \code{"singleTest"}.
#' Optionally, if the plotting function requires external packages, these can
Expand All @@ -403,6 +408,34 @@ addPlots <- function(study, plots, reset = FALSE) {
addElements(study, plots, reset)
}

#' Add mapping object
#'
#' Includes a mapping list connecting features across models.
#'
#' Mapping object consists of a list with element names matching the model
#' names, and each element consisting in a vector with feature IDs found in the
#' result object. For making meaningful connections between models, feature IDs
#' for distinct models must be aligned per index position in the vector.
#' E.g., if in a study there are models "transcriptomics" and "proteomics" and
#' the user wants to create a plot based on data from both, a mapping list with
#' element names "transcriptomics" and "proteomics" should be created, where
#' feature IDs of both models are found in the same index position in each list
#' element.
#'
#' @param mapping Feature IDs from models. The input object is a list object
#' with element names matching model names, and each element containing a
#' vector with feature IDs per model. Features with same index position across
#' models are considered found across models. For each model, the feature IDs
#' must match the feature IDs from results object of the respective model.
#' @inherit shared-add
#'
#' @seealso \code{\link{getPlottingData}}, \code{\link{plotStudy}}
#'
#' @export
addMapping <- function(study, mapping, reset = FALSE) {
addElements(study, mapping, reset)
}

#' Add barcode plot metadata
#'
#' The app can display a barcode plot of the enrichment results for a given
Expand Down
24 changes: 24 additions & 0 deletions R/check.R
Original file line number Diff line number Diff line change
Expand Up @@ -402,6 +402,30 @@ checkPlots <- function(plots) {
return(NULL)
}

checkMapping <- function(mapping) {
checkList(mapping)

mappingdf <- as.data.frame(mapping)

stopifnot(vapply(mappingdf, is.character, logical(1)))

# check if any given model has at least one feature aligned with another model
for (i in seq_along(mappingdf)) {
tempModel <- mappingdf[!is.na(mappingdf[[i]]),]
if (nrow(tempModel) > 1) {
featAligned <- any(apply(!sapply(tempModel, is.na), 1, sum) > 1)
} else {
featAligned <- any(sum(!sapply(tempModel, is.na)) > 1)
}

if (isFALSE(featAligned)) {
stop(sprintf("Model \"%s\" does not present any feature mapping to another model.", colnames(mappingdf)[[i]]))
}
}

return(NULL)
}

checkBarcodes <- function(barcodes) {
checkList(barcodes)

Expand Down
18 changes: 18 additions & 0 deletions R/get.R
Original file line number Diff line number Diff line change
Expand Up @@ -266,6 +266,24 @@ getPlots <- function(study, modelID = NULL, quiet = FALSE, libraries = NULL) {
)
}

#' Get mapping object from a study
#'
#' @inherit shared-get
#' @inheritParams listStudies
#'
#' @export
getMapping <- function(study, quiet = FALSE, libraries = NULL) {
getElements(
study,
elements = "mapping",
filters = list(),
default = "default",
fileType = "json",
quiet = quiet,
libraries = libraries
)
}

#' Get barcodes from a study
#'
#' @inherit shared-get
Expand Down
4 changes: 4 additions & 0 deletions R/sanitize.R
Original file line number Diff line number Diff line change
Expand Up @@ -74,6 +74,10 @@ sanitizePlots <- function(plots) {
return(plots)
}

sanitizeMapping <- function(mapping) {
return(mapping)
}

sanitizeBarcodes <- function(barcodes) {
return(barcodes)
}
Expand Down
27 changes: 27 additions & 0 deletions R/tests.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,8 @@ testStudy <- function(name,
resultsLinkouts = testResultsLinkouts(),
enrichmentsLinkouts = testEnrichmentsLinkouts(),
metaFeaturesLinkouts = testMetaFeaturesLinkouts(),
mapping = testMapping(seed = seed, nFeatures = nFeatures,
numericFeatureID = numericFeatureID),
version = version,
maintainer = maintainer,
maintainerEmail = maintainerEmail,
Expand Down Expand Up @@ -326,6 +328,31 @@ testPlots <- function() {
return(plots)
}

testMapping <- function(seed = 12345L, nFeatures = 100,
numericFeatureID = FALSE) {

results <- testResults(seed = seed, nFeatures = nFeatures,
numericFeatureID = numericFeatureID)

model_01_feats <- results[[1]][[1]][,1]
model_02_feats <- results[[2]][[1]][,1]

model_01_feats <- model_01_feats[order(model_01_feats)]
model_02_feats <- model_02_feats[order(model_02_feats)]

set.seed(1)
model_01_feats[which(model_01_feats %in% sample(model_01_feats, 10))] <- NA
set.seed(2)
model_02_feats[which(model_02_feats %in% sample(model_02_feats, 10))] <- NA

mapping <- list(
model_01 = model_01_feats,
model_02 = model_02_feats
)

return(mapping)
}

testBarcodes <- function(n = 3) {
barcodes <- list(
default = list(
Expand Down
32 changes: 32 additions & 0 deletions R/validate.R
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ validateStudy <- function(study) {
validateEnrichments(study)
validateEnrichmentsLinkouts(study)
validatePlots(study)
validateMapping(study)

return(invisible(TRUE))
}
Expand Down Expand Up @@ -312,3 +313,34 @@ validatePlots <- function(study) {

return(invisible(TRUE))
}

validateMapping <- function(study) {
mapping <- study[["mapping"]]

# Mapping isn't required
if (isEmpty(mapping)) return(NA)

# Check whether mapping names match model names from results table
models <- names(study[["results"]])
for (i in seq_along(mapping)) {
mappingID <- names(mapping[i])
if (!mappingID %in% models) {
stop("At least one mapping name does not match any model name from results table\n",
sprintf("mappingID: %s", mappingID))
}
}

# Check whether mapping features match results features
results <- getResults(study)
for (i in seq_along(mapping)) {
mappingID <- names(mapping[i])
mappingFeatures <- mapping[[i]][which(!is.na(mapping[[i]]))]
modelFeatures <- results[[grep(mappingID, models)]][1][[1]][,1]
if (!length(intersect(mappingFeatures, modelFeatures)) > 0) {
stop("Mapping features for modelID do not match features from modelID results table\n",
sprintf("modelID: %s", mappingID))
}
}
return(invisible(TRUE))
}

4 changes: 4 additions & 0 deletions inst/tinytest/testAdd.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

# Setup ------------------------------------------------------------------------

# source(paste0(getwd(), "/inst/tinytest/tinytestSettings.R"))
source("tinytestSettings.R")
using(ttdo)

Expand Down Expand Up @@ -44,6 +45,9 @@ study <- addMetaFeatures(study, metaFeatures = metaFeatures)
barcodes <- OmicNavigator:::testBarcodes()
study <- addBarcodes(study, barcodes = barcodes)

mapping <- OmicNavigator:::testMapping()
study <- addMapping(study, mapping = mapping)

reports <- OmicNavigator:::testReports()
study <- addReports(study, reports = reports)

Expand Down
6 changes: 6 additions & 0 deletions inst/tinytest/testCheck.R
Original file line number Diff line number Diff line change
Expand Up @@ -447,6 +447,12 @@ if (getRversion() > "4") {
)
}

# checkMapping -----------------------------------------------------------------

expect_error_xl(
addMapping(study, mapping = NULL)
)

# checkBarcodes ----------------------------------------------------------------

expect_error_xl(
Expand Down
23 changes: 23 additions & 0 deletions inst/tinytest/testGet.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

# Setup ------------------------------------------------------------------------

# source(paste0(getwd(), "/inst/tinytest/tinytestSettings.R"))
source("tinytestSettings.R")
using(ttdo)

Expand Down Expand Up @@ -597,6 +598,28 @@ expect_identical_xl(
testStudyObj[["plots"]][["model_03"]]
)

# getMapping -------------------------------------------------------------------

expect_identical_xl(
getMapping(testStudyObj),
testStudyObj[["mapping"]]
)

expect_message_xl(
getMapping(emptyStudy),
"No mapping available"
)

expect_error_xl(
getMapping(1),
"No method for object of class \"numeric\""
)

expect_error_xl(
getMapping(data.frame()),
"No method for object of class \"data.frame\""
)

# getBarcodes ------------------------------------------------------------------

expect_identical_xl(
Expand Down
13 changes: 13 additions & 0 deletions inst/tinytest/testGetNumeric.R
Original file line number Diff line number Diff line change
Expand Up @@ -146,6 +146,19 @@ expect_true_xl(
)
)

# getMapping -------------------------------------------------------------------

expect_identical_xl(
getMapping(testStudyObj),
testStudyObj[["mapping"]]
)

expect_true_xl(
is.character(
unlist(getMapping(testStudyObj))
)
)

# getBarcodeData ---------------------------------------------------------------

barcodeDataFromR <- getBarcodeData(
Expand Down
21 changes: 21 additions & 0 deletions inst/tinytest/testValidate.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

# Setup ------------------------------------------------------------------------

# source(paste0(getwd(), "/inst/tinytest/tinytestSettings.R"))
source("tinytestSettings.R")
using(ttdo)

Expand Down Expand Up @@ -236,3 +237,23 @@ expect_true_xl(
validateStudy(studyNoSamples),
info = "Samples not required to plot assays data"
)

# Mapping ----------------------------------------------------------------------

# Check if model names from mapping are not matching model names from results
invalidMapping <- testStudyObj
names(invalidMapping[["mapping"]]) <- c("model_01", "model")

expect_error_xl(
validateStudy(invalidMapping),
"At least one mapping name does not match any model name from results table\n"
)

# Check if features from mapping are not matching features from results
invalidMapping <- testStudyObj
invalidMapping[["mapping"]][["model_01"]] <- rep("non-matching feature", 100)

expect_error_xl(
validateStudy(invalidMapping),
"Mapping features for modelID do not match features from modelID results table\n"
)
Loading

0 comments on commit ec12603

Please sign in to comment.