Browse code

add metadata methods and append to outputs

LiNk-NY authored on 18/10/2024 22:04:04
Showing 1 changed files
... ...
@@ -69,6 +69,7 @@ setMethod("import", "TENxMTX", function(con, format, text, ...) {
69 69
     ## coerce to common use class
70 70
     mtxf <- as(mtxf, "CsparseMatrix")
71 71
     SummarizedExperiment(
72
-        assays = S4Vectors::SimpleList(counts = mtxf)
72
+        assays = S4Vectors::SimpleList(counts = mtxf),
73
+        metadata = metadata(con)
73 74
     )
74 75
 })
Browse code

compressed slot not needed in definition of TENxMTX when included in TENxFile

LiNk-NY authored on 19/01/2023 21:53:48
Showing 1 changed files
... ...
@@ -14,11 +14,7 @@
14 14
 #' @return A `TENxMTX` class object
15 15
 #'
16 16
 #' @exportClass TENxMTX
17
-.TENxMTX <- setClass(
18
-    Class = "TENxMTX",
19
-    contains = "TENxFile",
20
-    slots = c(compressed = "logical")
21
-)
17
+.TENxMTX <- setClass(Class = "TENxMTX", contains = "TENxFile")
22 18
 
23 19
 #' TENxMTX: Represent Matrix Market Format Files from 10X
24 20
 #'
Browse code

clarify doc re: return and use as(., 'CsparseMatrix')

LiNk-NY authored on 05/10/2022 18:07:31
Showing 1 changed files
... ...
@@ -8,8 +8,8 @@
8 8
 #'
9 9
 #' @details The `TENxMTX` class is a straightforward implementation that allows
10 10
 #'   the user to import a Matrix Market file format using `Matrix::readMM`.
11
-#'   Currently, it only supports return types of `dgCMatrix`. To request other
12
-#'   formats, please open an issue on GitHub.
11
+#'   Currently, it returns a `SummarizedExperiment` with an internal `dgCMatrix`
12
+#'   assay. To request other formats, please open an issue on GitHub.
13 13
 #'
14 14
 #' @return A `TENxMTX` class object
15 15
 #'
... ...
@@ -25,17 +25,17 @@
25 25
 #' This constructor function accepts `.mtx` and `.mtx.gz` compressed formats
26 26
 #' for eventual importing. It is mainly used with tarball files from 10X
27 27
 #' Genomics, where more annotation data is included. Importing solely the
28
-#' `.mtx` format will provide users with a sparse matrix of `dgCMatrix` class
29
-#' from the `Matrix` package. Currently, other formats are not supported but
30
-#' if you'd like to request support for a format, please open an issue on
31
-#' GitHub.
28
+#' `.mtx` format will provide users with a `SummarizedExperiment` with an assay
29
+#' of class `dgCMatrix` from the `Matrix` package. Currently, other formats are
30
+#' not supported but if you'd like to request support for a format, please open
31
+#' an issue on GitHub.
32 32
 #'
33 33
 #' @inheritParams TENxFile
34 34
 #'
35 35
 #' @param compressed logical(1) Whether the resource file is compressed (default
36 36
 #'   FALSE)
37 37
 #'
38
-#' @return A `SummarizedExperiment` instance
38
+#' @return A `SummarizedExperiment` instance with a `dgCMatrix` in the assay
39 39
 #'
40 40
 #' @examples
41 41
 #'
... ...
@@ -71,7 +71,7 @@ TENxMTX <- function(resource, compressed = FALSE, ...) {
71 71
 setMethod("import", "TENxMTX", function(con, format, text, ...) {
72 72
     mtxf <- Matrix::readMM(path(con))
73 73
     ## coerce to common use class
74
-    mtxf <- as(mtxf, "dgCMatrix")
74
+    mtxf <- as(mtxf, "CsparseMatrix")
75 75
     SummarizedExperiment(
76 76
         assays = S4Vectors::SimpleList(counts = mtxf)
77 77
     )
Browse code

add and update \value sections in docs

LiNk-NY authored on 24/08/2022 22:58:22
Showing 1 changed files
... ...
@@ -11,6 +11,8 @@
11 11
 #'   Currently, it only supports return types of `dgCMatrix`. To request other
12 12
 #'   formats, please open an issue on GitHub.
13 13
 #'
14
+#' @return A `TENxMTX` class object
15
+#'
14 16
 #' @exportClass TENxMTX
15 17
 .TENxMTX <- setClass(
16 18
     Class = "TENxMTX",
... ...
@@ -33,7 +35,7 @@
33 35
 #' @param compressed logical(1) Whether the resource file is compressed (default
34 36
 #'   FALSE)
35 37
 #'
36
-#' @return An instance of the `TENxMTX` class
38
+#' @return A `SummarizedExperiment` instance
37 39
 #'
38 40
 #' @examples
39 41
 #'
Browse code

add appropriate imports

LiNk-NY authored on 24/08/2022 22:57:28
Showing 1 changed files
... ...
@@ -61,6 +61,7 @@ TENxMTX <- function(resource, compressed = FALSE, ...) {
61 61
 #' @describeIn TENxMTX Import method mainly for mtx.gz files from 10x
62 62
 #'
63 63
 #' @importFrom S4Vectors SimpleList
64
+#' @importFrom Matrix readMM
64 65
 #'
65 66
 #' @inheritParams BiocIO::import
66 67
 #'
Browse code

update TENxMTX example with data

LiNk-NY authored on 03/08/2022 15:19:23
Showing 1 changed files
... ...
@@ -37,8 +37,13 @@
37 37
 #'
38 38
 #' @examples
39 39
 #'
40
-#' mtxf <-"~/data/10x/pbmc_3k/filtered_feature_bc_matrix/matrix.mtx.gz"
40
+#' mtxf <- system.file(
41
+#'     "extdata", "pbmc_3k_ff_bc_ex.mtx",
42
+#'     package = "TENxIO", mustWork = TRUE
43
+#' )
44
+#'
41 45
 #' con <- TENxMTX(mtxf)
46
+#'
42 47
 #' import(con)
43 48
 #'
44 49
 #' @export
Browse code

documentation updates

LiNk-NY authored on 14/07/2022 16:58:36
Showing 1 changed files
... ...
@@ -53,7 +53,12 @@ TENxMTX <- function(resource, compressed = FALSE, ...) {
53 53
     .TENxMTX(resource = resource, compressed = compr, extension = ext)
54 54
 }
55 55
 
56
+#' @describeIn TENxMTX Import method mainly for mtx.gz files from 10x
57
+#'
56 58
 #' @importFrom S4Vectors SimpleList
59
+#'
60
+#' @inheritParams BiocIO::import
61
+#'
57 62
 #' @export
58 63
 setMethod("import", "TENxMTX", function(con, format, text, ...) {
59 64
     mtxf <- Matrix::readMM(path(con))
Browse code

No need for double colons when in Depends field

LiNk-NY authored on 14/07/2022 02:32:16
Showing 1 changed files
... ...
@@ -59,7 +59,7 @@ setMethod("import", "TENxMTX", function(con, format, text, ...) {
59 59
     mtxf <- Matrix::readMM(path(con))
60 60
     ## coerce to common use class
61 61
     mtxf <- as(mtxf, "dgCMatrix")
62
-    SummarizedExperiment::SummarizedExperiment(
63
-        assays = SimpleList(counts = mtxf)
62
+    SummarizedExperiment(
63
+        assays = S4Vectors::SimpleList(counts = mtxf)
64 64
     )
65 65
 })
Browse code

import functions

LiNk-NY authored on 14/07/2022 02:31:42
Showing 1 changed files
... ...
@@ -53,6 +53,7 @@ TENxMTX <- function(resource, compressed = FALSE, ...) {
53 53
     .TENxMTX(resource = resource, compressed = compr, extension = ext)
54 54
 }
55 55
 
56
+#' @importFrom S4Vectors SimpleList
56 57
 #' @export
57 58
 setMethod("import", "TENxMTX", function(con, format, text, ...) {
58 59
     mtxf <- Matrix::readMM(path(con))
Browse code

add TENxIO-package.R and doc

LiNk-NY authored on 28/06/2022 19:58:14
Showing 1 changed files
... ...
@@ -53,7 +53,6 @@ TENxMTX <- function(resource, compressed = FALSE, ...) {
53 53
     .TENxMTX(resource = resource, compressed = compr, extension = ext)
54 54
 }
55 55
 
56
-#' @import SummarizedExperiment
57 56
 #' @export
58 57
 setMethod("import", "TENxMTX", function(con, format, text, ...) {
59 58
     mtxf <- Matrix::readMM(path(con))
Browse code

export MTX class and update docs

LiNk-NY authored on 28/06/2022 16:47:36
Showing 1 changed files
... ...
@@ -1,12 +1,40 @@
1 1
 #' TENxMTX: The Matrix Market representation class for 10X Data
2 2
 #'
3
+#' @description This class is designed to work with 10x MTX datasets,
4
+#'   particularly from the multiome pipelines.
3 5
 #'
6
+#' @slot compressed logical(1) Whether or not the file is in compressed format,
7
+#'   usually gzipped (`.gz`).
8
+#'
9
+#' @details The `TENxMTX` class is a straightforward implementation that allows
10
+#'   the user to import a Matrix Market file format using `Matrix::readMM`.
11
+#'   Currently, it only supports return types of `dgCMatrix`. To request other
12
+#'   formats, please open an issue on GitHub.
13
+#'
14
+#' @exportClass TENxMTX
4 15
 .TENxMTX <- setClass(
5 16
     Class = "TENxMTX",
6 17
     contains = "TENxFile",
7 18
     slots = c(compressed = "logical")
8 19
 )
9 20
 
21
+#' TENxMTX: Represent Matrix Market Format Files from 10X
22
+#'
23
+#' This constructor function accepts `.mtx` and `.mtx.gz` compressed formats
24
+#' for eventual importing. It is mainly used with tarball files from 10X
25
+#' Genomics, where more annotation data is included. Importing solely the
26
+#' `.mtx` format will provide users with a sparse matrix of `dgCMatrix` class
27
+#' from the `Matrix` package. Currently, other formats are not supported but
28
+#' if you'd like to request support for a format, please open an issue on
29
+#' GitHub.
30
+#'
31
+#' @inheritParams TENxFile
32
+#'
33
+#' @param compressed logical(1) Whether the resource file is compressed (default
34
+#'   FALSE)
35
+#'
36
+#' @return An instance of the `TENxMTX` class
37
+#'
10 38
 #' @examples
11 39
 #'
12 40
 #' mtxf <-"~/data/10x/pbmc_3k/filtered_feature_bc_matrix/matrix.mtx.gz"
Browse code

update TENxMTX constructor

LiNk-NY authored on 22/06/2022 18:09:10
Showing 1 changed files
... ...
@@ -1,13 +1,36 @@
1
+#' TENxMTX: The Matrix Market representation class for 10X Data
2
+#'
3
+#'
1 4
 .TENxMTX <- setClass(
2 5
     Class = "TENxMTX",
3
-    contains = "TENxFile"
6
+    contains = "TENxFile",
7
+    slots = c(compressed = "logical")
4 8
 )
5 9
 
10
+#' @examples
11
+#'
12
+#' mtxf <-"~/data/10x/pbmc_3k/filtered_feature_bc_matrix/matrix.mtx.gz"
13
+#' con <- TENxMTX(mtxf)
14
+#' import(con)
15
+#'
16
+#' @export
17
+TENxMTX <- function(resource, compressed = FALSE, ...) {
18
+    dots <- list(...)
19
+    ext <- dots[["extension"]]
20
+    if (is.null(ext))
21
+        ext <- .get_ext(resource)
22
+    compr <- identical(ext, "mtx.gz")
23
+    if (!ext %in% c("mtx.gz", "mtx"))
24
+        warning("File extension is not 'mtx'; import may fail", call. = FALSE)
25
+    .TENxMTX(resource = resource, compressed = compr, extension = ext)
26
+}
27
+
6 28
 #' @import SummarizedExperiment
7 29
 #' @export
8 30
 setMethod("import", "TENxMTX", function(con, format, text, ...) {
9
-    mtxf <- SingleCellMultiModal:::.read_mtx(path(con))
10
-    ## TODO: make use of other files
31
+    mtxf <- Matrix::readMM(path(con))
32
+    ## coerce to common use class
33
+    mtxf <- as(mtxf, "dgCMatrix")
11 34
     SummarizedExperiment::SummarizedExperiment(
12 35
         assays = SimpleList(counts = mtxf)
13 36
     )
Browse code

organize files

LiNk-NY authored on 02/06/2022 14:44:32
Showing 1 changed files
1 1
new file mode 100644
... ...
@@ -0,0 +1,14 @@
1
+.TENxMTX <- setClass(
2
+    Class = "TENxMTX",
3
+    contains = "TENxFile"
4
+)
5
+
6
+#' @import SummarizedExperiment
7
+#' @export
8
+setMethod("import", "TENxMTX", function(con, format, text, ...) {
9
+    mtxf <- SingleCellMultiModal:::.read_mtx(path(con))
10
+    ## TODO: make use of other files
11
+    SummarizedExperiment::SummarizedExperiment(
12
+        assays = SimpleList(counts = mtxf)
13
+    )
14
+})