Skip to content

Commit

Permalink
Merge pull request #19 from Samson-Dai/main
Browse files Browse the repository at this point in the history
Solve Gene's Issue
  • Loading branch information
Tim committed Apr 7, 2022
2 parents 9f6a5de + ca758ba commit 191c324
Show file tree
Hide file tree
Showing 3 changed files with 44 additions and 12 deletions.
44 changes: 34 additions & 10 deletions R/initialize_in_memory.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@
#' @param features_df a data frame giving the names of the features. The first column (required) contains the feature IDs (e.g., ENSG00000186092), and the second column (optional) contains the human-readable feature names (e.g., OR4F5). Subsequent columns are discarded. Gene names starting with "MT-" are assumed to be mitochondrial genes and will be used to compute the p_mito covariate.
#' @param odm_fp location to write the backing .odm file.
#' @param metadata_fp (optional; default NULL) location to write the metadata .RDS file. By default, a file called "metadata.rds" stored in the same directory as the backing .odm file.
#' @param gene_access_only a boolean value, TRUE if only allow gene-wise access; FALSE if allow both gene-wise and cell-wise access
#'
#' @return A `covariate_ondisc_matrix` object.
#' @export
Expand Down Expand Up @@ -43,7 +44,7 @@
#' odm_fp <- paste0(create_new_directory(), "/logical_odm")
#' odm_logical <- create_ondisc_matrix_from_R_matrix(r_matrix_2, barcodes,
#' features_df_2, odm_fp)
create_ondisc_matrix_from_R_matrix <- function(r_matrix, barcodes, features_df, odm_fp, metadata_fp = NULL) {
create_ondisc_matrix_from_R_matrix <- function(r_matrix, barcodes, features_df, odm_fp, metadata_fp = NULL, gene_access_only = FALSE) {
# generate random ODM ID
odm_id <- sample(seq(0L, .Machine$integer.max), size = 1)

Expand Down Expand Up @@ -105,16 +106,36 @@ create_ondisc_matrix_from_R_matrix <- function(r_matrix, barcodes, features_df,
repr = "R",
index1 = FALSE,
x = r_matrix@x)
} else { # dense case
} else if (is(r_matrix, "dgRMatrix")) { # CSR format
r_matrix_t <- Matrix::t(r_matrix)
csc_r_matrix <- Matrix::sparseMatrix(i = r_matrix_t@j,
p = r_matrix_t@p,
dims = r_matrix@Dim,
repr = "C",
index1 = FALSE,
x = r_matrix_t@x)
csr_r_matrix <- r_matrix
} else if (is(r_matrix, "dgCMatrix")) { # CSC format
csc_r_matrix <- r_matrix
r_matrix_t <- Matrix::t(r_matrix)
csr_r_matrix <- Matrix::sparseMatrix(j = r_matrix_t@i,
p = r_matrix_t@p,
dims = r_matrix@Dim,
repr = "R",
index1 = FALSE,
x = r_matrix_t@x)
} else if (is(r_matrix, "matrix")){ # dense case
csc_r_matrix <- as(r_matrix, "dgCMatrix")
csr_r_matrix <- as(r_matrix, "dgRMatrix")
} else { #invalid input
stop("Input matrix must be a class of matrix, dgTMatrix, dgCMatrix, or dgRMatrix.")
}

# initialize the ODM
initialize_h5_file_on_disk(odm_fp, bag_of_variables, odm_id)

# Write in memory matrix to the .h5 file on-disk (side-effect)
write_matrix_to_h5(odm_fp, expression_metadata = bag_of_variables, csc_r_matrix = csc_r_matrix, csr_r_matrix = csr_r_matrix)
write_matrix_to_h5(odm_fp, expression_metadata = bag_of_variables, csc_r_matrix = csc_r_matrix, csr_r_matrix = csr_r_matrix, gene_access_only = gene_access_only)

### STEP3: Prepare output
odm <- ondisc_matrix(h5_file = odm_fp,
Expand Down Expand Up @@ -170,18 +191,21 @@ get_expression_metadata_from_r_matrix <- function(r_matrix) {
#' @param features_df a data frame giving the names of the features. The first column (required) contains the feature IDs (e.g., ENSG00000186092), and the second column (optional) contains the human-readable feature names (e.g., OR4F5). Subsequent columns are discarded. Gene names starting with "MT-" are assumed to be mitochondrial genes and will be used to compute the p_mito covariate.
#' @param csc_r_matrix a Matrix csc representation of the r matrix
#' @param csr_r_matrix a Matrix csr representation of the r matrix
#' @param gene_access_only a boolean value, TRUE if only allow gene-wise access; FALSE if allow both gene-wise and cell-wise access
#'
#' @return NULL
#' @noRd
write_matrix_to_h5 <- function(odm_fp, expression_metadata, csc_r_matrix, csr_r_matrix) {
# Write CSC
rhdf5::h5write(csc_r_matrix@p, file = odm_fp, name="cell_ptr")
rhdf5::h5write(csc_r_matrix@i, file = odm_fp, name="feature_idxs")
if (!expression_metadata$is_logical) {
rhdf5::h5write(csc_r_matrix@x, file = odm_fp, name="data_csc")
write_matrix_to_h5 <- function(odm_fp, expression_metadata, csc_r_matrix, csr_r_matrix, gene_access_only) {
# Write CSC, cell-wise access
if (!gene_access_only) {
rhdf5::h5write(csc_r_matrix@p, file = odm_fp, name="cell_ptr")
rhdf5::h5write(csc_r_matrix@i, file = odm_fp, name="feature_idxs")
if (!expression_metadata$is_logical) {
rhdf5::h5write(csc_r_matrix@x, file = odm_fp, name="data_csc")
}
}

# Write CSR
# Write CSR, gene-wise access
rhdf5::h5write(csr_r_matrix@p, file = odm_fp, name = "feature_ptr")
rhdf5::h5write(csr_r_matrix@j, file = odm_fp, name = "cell_idxs")
if (!expression_metadata$is_logical) {
Expand Down
5 changes: 4 additions & 1 deletion man/create_ondisc_matrix_from_R_matrix.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 6 additions & 1 deletion tests/testthat/test-in_memory_initialize.R
Original file line number Diff line number Diff line change
@@ -1,7 +1,12 @@
# Initialize metadata odms from in-memory R objects in different directories
cov_odms_from_memory <- lapply(r_mats_plus_metadata, function(l) {
file_dir <- create_new_directory()
metadata_odm <- create_ondisc_matrix_from_R_matrix(r_matrix = as.matrix(l$r_mat),
# randomly choose the class of matrix
r_matrix <- as.matrix(l$r_mat)
matrix_class <- sample(c("dgTMatrix", "dgRMatrix", "dgCMatrix", "matrix"), 1)
r_matrix <- as(r_matrix, matrix_class)

metadata_odm <- create_ondisc_matrix_from_R_matrix(r_matrix = r_matrix,
barcodes = l$barcodes,
features_df = l$features_df,
odm_fp = file_dir)
Expand Down

0 comments on commit 191c324

Please sign in to comment.