Skip to content

Commit

Permalink
fix as.matrix() to actually return a matrix.
Browse files Browse the repository at this point in the history
  • Loading branch information
lschneiderbauer committed Dec 27, 2024
1 parent 028e20d commit 4cdb003
Show file tree
Hide file tree
Showing 2 changed files with 21 additions and 2 deletions.
8 changes: 6 additions & 2 deletions R/fcwtr_scalogram.R
Original file line number Diff line number Diff line change
Expand Up @@ -344,7 +344,7 @@ as.data.frame.fcwtr_scalogram <- function(x, ...) {
#' An "fcwtr_scalogram" object resulting from [fcwt()].
#' @inheritParams base::as.matrix
#'
#' @return A two dimensional numeric vector, inheriting the S3 class "matrix".
#' @return A two dimensional numeric vector, inheriting the class "matrix".
#'
#' @examples
#' fcwt(
Expand All @@ -356,9 +356,13 @@ as.data.frame.fcwtr_scalogram <- function(x, ...) {
#'
#' @export
as.matrix.fcwtr_scalogram <- function(x, ...) {
t <- sc_dim_time(x)
f <- sc_dim_freq(x)

attributes(x) <- NULL
dim(x) <- c(t, f)

unclass(x)
x
}

#' Extract parts of a scalogram
Expand Down
15 changes: 15 additions & 0 deletions tests/testthat/test-fcwtr_scalogram.R
Original file line number Diff line number Diff line change
Expand Up @@ -90,6 +90,21 @@ test_that("as.data.frame() result has correct properties", {
expect_true(has_comp_unit(res[["freq"]], "Hz"))
})

test_that("as.matrix() has the correct S3 class", {
expect_true(
fcwt(
ts_sin_440[1:1000],
sample_freq = 44100,
freq_begin = 50,
freq_end = 1000,
n_freqs = 10,
sigma = 1
) |>
as.matrix() |>
is.matrix()
)
})

test_that("`agg()` does not err", {
prep <-
fcwt(
Expand Down

0 comments on commit 4cdb003

Please sign in to comment.