... | ... |
@@ -326,7 +326,7 @@ import_association_file <- function(path, |
326 | 326 |
parsing_problems <- af_checks$parsing_probs |
327 | 327 |
date_problems <- af_checks$date_probs |
328 | 328 |
checks <- af_checks$check |
329 |
- if (nrow(parsing_problems) == 0) { |
|
329 |
+ if (is.null(parsing_problems) || nrow(parsing_problems) == 0) { |
|
330 | 330 |
parsing_problems <- NULL |
331 | 331 |
} |
332 | 332 |
if (is.null(date_problems) || nrow(date_problems) == 0) { |
... | ... |
@@ -582,6 +582,31 @@ test_that("as_sparse_matrix works with list of matrices", { |
582 | 582 |
expect_equal(nrow(sparse[[2]]), 3) |
583 | 583 |
}) |
584 | 584 |
|
585 |
+test_that("as_sparse_matrix works with aggreg matrix", { |
|
586 |
+ smpl_agg <- tibble::tibble( |
|
587 |
+ chr = c(1, 2, 3), |
|
588 |
+ integration_locus = c(1354, 5634, 4765), |
|
589 |
+ strand = c("+", "+", "+"), |
|
590 |
+ GeneName = c("GENE1", "GENE2", "GENE3"), |
|
591 |
+ GeneStrand = c("+", "+", "+"), |
|
592 |
+ SubjectID = c("S1", "S2", "S2"), |
|
593 |
+ CellMarker = c("C1", "C1", "C2"), |
|
594 |
+ Value_sum = c(46, 546, 587) |
|
595 |
+ ) |
|
596 |
+ sparse <- as_sparse_matrix(smpl_agg, |
|
597 |
+ single_value_col = "Value_sum", |
|
598 |
+ key = c("SubjectID", "CellMarker")) |
|
599 |
+ expected <- tibble::tibble(chr = c(1, 2, 3), |
|
600 |
+ integration_locus = c(1354, 5634, 4765), |
|
601 |
+ strand = c('+', '+', '+'), |
|
602 |
+ GeneName = c('GENE1', 'GENE2', 'GENE3'), |
|
603 |
+ GeneStrand = c('+', '+', '+'), |
|
604 |
+ S1_C1 = c(46, NA, NA), |
|
605 |
+ S2_C1 = c(NA, 546, NA), |
|
606 |
+ S2_C2 = c(NA, NA, 587)) |
|
607 |
+ expect_equal(sparse, expected) |
|
608 |
+}) |
|
609 |
+ |
|
585 | 610 |
#------------------------------------------------------------------------------# |
586 | 611 |
# Tests annotation_issues |
587 | 612 |
#------------------------------------------------------------------------------# |