Browse code

Updated featureModuleLookup to be able to search rowData

Joshua D. Campbell authored on 10/07/2021 13:47:41
Showing 3 changed files

... ...
@@ -1,25 +1,31 @@
1 1
 #' @title Obtain the gene module of a gene of interest
2 2
 #' @description This function will output the corresponding feature module for
3 3
 #'  a specified vector of genes from a celda_CG or celda_G \code{celdaModel}.
4
-#'  \code{feature} must match the rownames of \code{sce}.
4
+#'  \code{features} must match the rownames of \code{sce}.
5 5
 #' @param sce A \linkS4class{SingleCellExperiment} object returned by
6 6
 #'  \link{celda_G}, or \link{celda_CG}, with the matrix
7 7
 #'  located in the \code{useAssay} assay slot.
8 8
 #'  Rows represent features and columns represent cells.
9
-#' @param feature Character vector. Identify feature modules for the specified
9
+#' @param features Character vector. Identify feature modules for the specified
10 10
 #'  feature names. \code{feature} must match the rownames of \code{sce}.
11 11
 #' @param altExpName The name for the \link{altExp} slot
12 12
 #'  to use. Default "featureSubset".
13 13
 #' @param exactMatch Logical. Whether to look for exactMatch of the gene name
14 14
 #'  within counts matrix. Default \code{TRUE}.
15
-#' @return List. Each entry corresponds to the feature module determined for
16
-#' the provided features.
15
+#' @param by Character. Where to search for \code{features} in the sce object.
16
+#' If set to \code{"rownames"} then the features will be searched for among
17
+#' rownames(sce). This can also be set to one of the \code{colnames} of
18
+#' rowData(sce). Default \code{"rownames"}.
19
+#' @return Numeric vector containing the module numbers for each feature. If
20
+#' the feature was not found, then an \code{NA} value will be returned in that
21
+#' position. If no features were found, then an error will be given.
17 22
 #' @export
18 23
 setGeneric("featureModuleLookup",
19 24
     function(sce,
20
-        feature,
25
+        features,
21 26
         altExpName = "featureSubset",
22
-        exactMatch = TRUE) {
27
+        exactMatch = TRUE,
28
+        by = "rownames") {
23 29
 
24 30
         standardGeneric("featureModuleLookup")})
25 31
 
... ...
@@ -27,57 +33,32 @@ setGeneric("featureModuleLookup",
27 33
 #' @examples
28 34
 #' data(sceCeldaCG)
29 35
 #' module <- featureModuleLookup(sce = sceCeldaCG,
30
-#'     feature = c("Gene_1", "Gene_XXX"))
36
+#'     features = c("Gene_1", "Gene_XXX"))
31 37
 #' @export
32 38
 #' @rdname featureModuleLookup
33 39
 setMethod("featureModuleLookup", signature(sce = "SingleCellExperiment"),
34 40
     function(sce,
35
-        feature,
41
+        features,
36 42
         altExpName = "featureSubset",
37
-        exactMatch = TRUE) {
43
+        exactMatch = TRUE,
44
+        by = "rownames") {
38 45
 
39
-        altExp <- SingleCellExperiment::altExp(sce, altExpName)
46
+        modules <- as.numeric(celdaModules(sce, altExpName = altExpName))
47
+        
40 48
         if (celdaModel(sce, altExpName = altExpName) %in%
41 49
                 c("celda_CG", "celda_G")) {
42
-            featureList <- .featureModuleLookup(sce = altExp,
43
-                feature = feature,
44
-                exactMatch = exactMatch)
50
+          altExp <- SingleCellExperiment::altExp(sce, altExpName)
51
+          featureIndex <- retrieveFeatureIndex(features, x = altExp,
52
+                exactMatch = exactMatch, by = by)
53
+          featureModules <- modules[featureIndex]
54
+          names(featureModules) <- features  
45 55
         } else {
46 56
             stop("S4Vectors::metadata(altExp(sce, altExpName))$",
47 57
                 "celda_parameters$model must be",
48 58
                 " one of 'celda_G', or 'celda_CG'")
49 59
         }
50
-        return(featureList)
60
+        return(featureModules)
51 61
     }
52 62
 )
53 63
 
54 64
 
55
-.featureModuleLookup <- function(sce, feature, exactMatch) {
56
-    if (!isTRUE(exactMatch)) {
57
-        feature <- unlist(lapply(
58
-            seq(length(feature)),
59
-            function(x) {
60
-                rownames(sce)[grep(feature[x], rownames(sce))]
61
-            }
62
-        ))
63
-    }
64
-
65
-    featList <- lapply(
66
-        seq(length(feature)),
67
-        function(x) {
68
-            if (feature[x] %in% rownames(sce)) {
69
-                return(SummarizedExperiment::rowData(
70
-                    sce)$celda_feature_module[which(rownames(sce) ==
71
-                        feature[x])])
72
-            } else {
73
-                return(paste0(
74
-                    "No feature was identified matching '",
75
-                    feature[x],
76
-                    "'."
77
-                ))
78
-            }
79
-        }
80
-    )
81
-    names(featList) <- feature
82
-    return(featList)
83
-}
... ...
@@ -7,16 +7,18 @@
7 7
 \usage{
8 8
 featureModuleLookup(
9 9
   sce,
10
-  feature,
10
+  features,
11 11
   altExpName = "featureSubset",
12
-  exactMatch = TRUE
12
+  exactMatch = TRUE,
13
+  by = "rownames"
13 14
 )
14 15
 
15 16
 \S4method{featureModuleLookup}{SingleCellExperiment}(
16 17
   sce,
17
-  feature,
18
+  features,
18 19
   altExpName = "featureSubset",
19
-  exactMatch = TRUE
20
+  exactMatch = TRUE,
21
+  by = "rownames"
20 22
 )
21 23
 }
22 24
 \arguments{
... ...
@@ -25,7 +27,7 @@ featureModuleLookup(
25 27
 located in the \code{useAssay} assay slot.
26 28
 Rows represent features and columns represent cells.}
27 29
 
28
-\item{feature}{Character vector. Identify feature modules for the specified
30
+\item{features}{Character vector. Identify feature modules for the specified
29 31
 feature names. \code{feature} must match the rownames of \code{sce}.}
30 32
 
31 33
 \item{altExpName}{The name for the \link{altExp} slot
... ...
@@ -33,18 +35,24 @@ to use. Default "featureSubset".}
33 35
 
34 36
 \item{exactMatch}{Logical. Whether to look for exactMatch of the gene name
35 37
 within counts matrix. Default \code{TRUE}.}
38
+
39
+\item{by}{Character. Where to search for \code{features} in the sce object.
40
+If set to \code{"rownames"} then the features will be searched for among
41
+rownames(sce). This can also be set to one of the \code{colnames} of
42
+rowData(sce). Default \code{"rownames"}.}
36 43
 }
37 44
 \value{
38
-List. Each entry corresponds to the feature module determined for
39
-the provided features.
45
+Numeric vector containing the module numbers for each feature. If
46
+the feature was not found, then an \code{NA} value will be returned in that
47
+position. If no features were found, then an error will be given.
40 48
 }
41 49
 \description{
42 50
 This function will output the corresponding feature module for
43 51
  a specified vector of genes from a celda_CG or celda_G \code{celdaModel}.
44
- \code{feature} must match the rownames of \code{sce}.
52
+ \code{features} must match the rownames of \code{sce}.
45 53
 }
46 54
 \examples{
47 55
 data(sceCeldaCG)
48 56
 module <- featureModuleLookup(sce = sceCeldaCG,
49
-    feature = c("Gene_1", "Gene_XXX"))
57
+    features = c("Gene_1", "Gene_XXX"))
50 58
 }
... ...
@@ -182,11 +182,7 @@ test_that(desc = "Testing featureModuleLookup with celda_CG", {
182 182
     res <- featureModuleLookup(modelCG, "Gene_1")
183 183
     expect_true(res == celdaModules(modelCG)[1])
184 184
 
185
-    res <- featureModuleLookup(modelCG, "Gene_2", exactMatch = FALSE)
186
-    expect_true(length(res) == 11)
187
-
188
-    res <- featureModuleLookup(modelCG, "XXXXXXX")
189
-    expect_true(grepl("No feature", res))
185
+    expect_error(featureModuleLookup(modelCG, "XXXXXXX"))
190 186
 })
191 187
 
192 188