Skip to content

Commit

Permalink
add apply method
Browse files Browse the repository at this point in the history
  • Loading branch information
Yunuuuu committed Jul 5, 2024
1 parent 34f0d5c commit 0eb063b
Show file tree
Hide file tree
Showing 9 changed files with 250 additions and 21 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,7 @@ Collate:
'Method-RenameDims.R'
'Method-Subassign.R'
'Method-Subset.R'
'Method-apply.R'
'Method-axis.R'
'Method-crossprod.R'
'Method-internal.R'
Expand Down
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ exportMethods(OLD_extract_sparse_array)
exportMethods(Ops)
exportMethods(acbind)
exportMethods(aperm)
exportMethods(apply)
exportMethods(arbind)
exportMethods(as.array)
exportMethods(as.matrix)
Expand Down Expand Up @@ -167,6 +168,7 @@ importFrom(DelayedArray,"type<-")
importFrom(DelayedArray,DelayedArray)
importFrom(DelayedArray,OLD_extract_sparse_array)
importFrom(DelayedArray,acbind)
importFrom(DelayedArray,apply)
importFrom(DelayedArray,arbind)
importFrom(DelayedArray,cbind)
importFrom(DelayedArray,chunkdim)
Expand Down
8 changes: 7 additions & 1 deletion R/Class-BPCellsMatrix.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,13 @@ NULL
#' only support 2-dim array.
#' @export
#' @rdname BPCellsMatrix-class
BPCellsArray <- function(x) DelayedArray(x)
BPCellsArray <- function(x) {
if (!(methods::is(x, "BPCellsDelayedOp") ||
methods::is(x, "IterableMatrix"))) {
x <- BPCellsSeed(x)
}
DelayedArray(x)
}

#' @export
#' @rdname BPCellsMatrix-class
Expand Down
88 changes: 88 additions & 0 deletions R/Method-apply.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,88 @@
#' Apply Functions Over matrix Margins
#'
#' @param X A `r rd_matrix()`.
#' @param MARGIN A single number giving the subscripts which the function will
#' be applied over, `1` indicates rows, `2` indicates columns.
#' @param FUN Function to be applied. `FUN` is found by a call to [match.fun]
#' and typically is either a function or a symbol (e.g., a backquoted name) or a
#' character string specifying a function to be searched for from the
#' environment of the call to apply.
#' @inheritParams base::apply
#' @return
#' If each call to `FUN` returns a vector of length `n`, and simplify is `TRUE`,
#' then `apply` returns an array of dimension `c(n, dim(X)[MARGIN])` if `n > 1`.
#' If `n` equals `1`, `apply` returns a vector if `MARGIN` has length 1 and an
#' array of dimension `dim(X)[MARGIN]` otherwise. If `n` is `0`, the result has
#' length 0 but not necessarily the ‘correct’ dimension.
#'
#' If the calls to `FUN` return vectors of different lengths, or if `simplify`
#' is `FALSE`, `apply` returns a list of length `dim(X)[MARGIN]`.
#' @importFrom DelayedArray apply
#' @aliases apply
#' @export
methods::setMethod(
"apply", "BPCellsMatrix",
function(X, MARGIN, FUN, ..., simplify = TRUE) {
assert_number(MARGIN)
FUN <- match.fun(FUN)
X_dim <- dim(X)
MARGIN <- as.integer(MARGIN)
if (MARGIN < 1L || MARGIN > length(X_dim)) {
cli::cli_abort(
"{.arg MARGIN} must be >= 1 and <= length(dim(X))"
)
}
if (X_dim[[MARGIN]] == 0L) {
## base::apply seems to be doing something like that!
ans <- FUN(X, ...)
return(as.vector(ans[0L]))
}
seed <- to_BPCells(X@seed)
values <- integer(dim(seed)[3L - MARGIN]) # nolint
nms <- switch(MARGIN,
rownames(seed),
colnames(seed)
)
.fun <- switch(MARGIN,
function(.value, .row_index, .col_index, ...) {
# restore zero values
values[.col_index] <- .value
FUN(values, ...)
},
function(.value, .row_index, .col_index, ...) {
# restore zero values
values[.row_index] <- .value
FUN(values, ...)
}
)
ans <- switch(MARGIN,
{
if (BPCells::storage_order(seed) == "col") {
seed <- BPCells::transpose_storage_order(seed)
}
BPCells::apply_by_row(mat = seed, fun = .fun, ...)
},
{
if (BPCells::storage_order(seed) == "row") {
seed <- BPCells::transpose_storage_order(seed)
}
BPCells::apply_by_col(mat = seed, fun = .fun, ...)
}
)
if (simplify) {
lens <- lengths(ans)
if (all(lens == .subset(lens, 1L))) {
if (.subset(lens, 1L) == 1L) {
ans <- unlist(ans, recursive = FALSE, use.names = FALSE)
names(ans) <- nms
} else {
ans <- do.call(cbind, ans)
colnames(ans) <- nms
}
}
} else {
names(ans) <- nms
}
ans
}
)
30 changes: 30 additions & 0 deletions R/import-standalone-assert.R
Original file line number Diff line number Diff line change
Expand Up @@ -152,6 +152,36 @@ assert_bool <- function(
FALSE
}

assert_number <- function(
x, na_ok = FALSE, show_length = TRUE, ...,
arg = rlang::caller_arg(x),
call = rlang::caller_env()) {
what <- "a number"
if (na_ok) {
what <- c(what, style_code("NA"))
}
assert_(
x = x,
assert_fn = function(x) {
.rlang_check_is_number(x, na_ok = na_ok)
}, what = what,
show_length = show_length,
...,
arg = arg,
call = call
)
}

.rlang_check_is_number <- function(x, na_ok) {
if (is.numeric(x) && length(x) == 1L) {
return(TRUE)
}
if (na_ok && identical(x, NA)) {
return(TRUE)
}
FALSE
}

# atomic vector ------------------------------------
is_character <- function(x, empty_ok = TRUE, na_ok = TRUE) {
out <- is.character(x)
Expand Down
21 changes: 11 additions & 10 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ been optimized by `c++` or `c`. Although `DelayedArray` package provides
block processing for most usual operations, `BPCellsArray` re-dispatch
these methods to use the optimized methods in BPCells.

Here is a summarized delayed operations in BPCells:
Here is a summarized delayed operations in `BPCellsArray`:

| Operations | BPCells | BPCellsArray |
|------------------------------------------|-----------------------------|----------------------------------------|
Expand All @@ -74,15 +74,16 @@ Here is a summarized delayed operations in BPCells:

Other non-lazied operations:

| Operations | BPCells | BPCellsArray | Note |
|--------------------------|--------------------------|---------------------------------|------------------|
| row/col summarize | matrix_stats | matrix_stats | |
| row summarize | rowSums,rowMeans,rowVars | rowSums,rowMeans,rowVars,rowSds | |
| col summarize | colSums,colMeans,colVars | colSums,colMeans,colVars,colSds | |
| Multiplication | %\*% | %\*% | For some methods |
| Crossproduct | | crossprod | For some methods |
| Matrix product transpose | | tcrossprod | For some methods |
| svd | svds | `runSVD`+`SpectraParam` | |
| Operations | BPCells | BPCellsArray | Note |
|--------------------------|--------------------------------|---------------------------------|------------------|
| row/col summarize | matrix_stats | matrix_stats | |
| row summarize | rowSums,rowMeans,rowVars | rowSums,rowMeans,rowVars,rowSds | |
| col summarize | colSums,colMeans,colVars | colSums,colMeans,colVars,colSds | |
| Multiplication | %\*% | %\*% | For some methods |
| Crossproduct | | crossprod | For some methods |
| Matrix product transpose | | tcrossprod | For some methods |
| svd | svds | `runSVD`+`SpectraParam` | |
| apply | `apply_by_row`, `apply_by_col` | apply | |

## Matrix Storage Format

Expand Down
38 changes: 38 additions & 0 deletions man/apply-BPCellsMatrix-method.Rd

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

62 changes: 62 additions & 0 deletions tests/testthat/setup.R
Original file line number Diff line number Diff line change
Expand Up @@ -499,4 +499,66 @@ test_methods <- function(
testthat::expect_error(1 / obj)
}
)

cli::cli_inform("{.field apply} for seed {name} works as expected")
testthat::test_that(
sprintf("`apply` for seed %s works as expected", name),
{
obj <- BPCellsArray(obj)
# row operations --------------------------
testthat::expect_equal(apply(obj, 1, sum), apply(mat, 1, sum))
testthat::expect_equal(
apply(transpose_axis(obj), 1, sum),
apply(mat, 1, sum)
)

testthat::expect_equal(apply(obj, 1, mean), apply(mat, 1, mean))
testthat::expect_equal(
apply(transpose_axis(obj), 1, mean),
apply(mat, 1, mean)
)

testthat::expect_equal(
apply(obj, 1, stats::quantile),
apply(mat, 1, stats::quantile)
)
testthat::expect_equal(
apply(obj, 1, stats::quantile, simplify = FALSE),
apply(mat, 1, stats::quantile, simplify = FALSE)
)
testthat::expect_equal(
apply(transpose_axis(obj), 1, stats::quantile),
apply(mat, 1, stats::quantile)
)


# column operations --------------------------
testthat::expect_equal(apply(obj, 2L, sum), apply(mat, 2L, sum))
testthat::expect_equal(
apply(transpose_axis(obj), 2L, sum),
apply(mat, 2L, sum)
)


testthat::expect_equal(apply(obj, 2L, mean), apply(mat, 2L, mean))
testthat::expect_equal(
apply(transpose_axis(obj), 2L, mean),
apply(mat, 2L, mean)
)


testthat::expect_equal(
apply(obj, 2L, stats::quantile),
apply(mat, 2L, stats::quantile)
)
testthat::expect_equal(
apply(obj, 2L, stats::quantile, simplify = FALSE),
apply(mat, 2L, stats::quantile, simplify = FALSE)
)
testthat::expect_equal(
apply(transpose_axis(obj), 2L, stats::quantile),
apply(mat, 2L, stats::quantile)
)
}
)
}
21 changes: 11 additions & 10 deletions vignettes/BPCellsArray.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ R object or written to disk. And most operations have been optimized by `c++` or
operations, `BPCellsArray` re-dispatch these methods to use the optimized
methods in BPCells.

Here is a summarized delayed operations in BPCells:
Here is a summarized delayed operations in `BPCellsArray`:

| Operations | BPCells | BPCellsArray |
| ---------------------------------------- | ---------------------------- | -------------------------------------- |
Expand Down Expand Up @@ -83,15 +83,16 @@ Here is a summarized delayed operations in BPCells:

Other non-lazied operations:

| Operations | BPCells | BPCellsArray | Note |
| ------------------------ | ------------------------ | ------------------------------- | ---------------- |
| row/col summarize | matrix_stats | matrix_stats | |
| row summarize | rowSums,rowMeans,rowVars | rowSums,rowMeans,rowVars,rowSds | |
| col summarize | colSums,colMeans,colVars | colSums,colMeans,colVars,colSds | |
| Multiplication | %*% | %*% | For some methods |
| Crossproduct | | crossprod | For some methods |
| Matrix product transpose | | tcrossprod | For some methods |
| svd | svds | `runSVD`+`SpectraParam` | |
| Operations | BPCells | BPCellsArray | Note |
| ------------------------ | ------------------------------ | ------------------------------- | ---------------- |
| row/col summarize | matrix_stats | matrix_stats | |
| row summarize | rowSums,rowMeans,rowVars | rowSums,rowMeans,rowVars,rowSds | |
| col summarize | colSums,colMeans,colVars | colSums,colMeans,colVars,colSds | |
| Multiplication | %*% | %*% | For some methods |
| Crossproduct | | crossprod | For some methods |
| Matrix product transpose | | tcrossprod | For some methods |
| svd | svds | `runSVD`+`SpectraParam` | |
| apply | `apply_by_row`, `apply_by_col` | apply | |

## Matrix Storage Format
BPCells provide following formats:
Expand Down

0 comments on commit 0eb063b

Please sign in to comment.