Skip to content

Commit

Permalink
add S3 methods: as.matrix, print, adjust docs
Browse files Browse the repository at this point in the history
  • Loading branch information
lschneiderbauer committed Dec 27, 2024
1 parent 27ae0ed commit 2942add
Show file tree
Hide file tree
Showing 11 changed files with 111 additions and 17 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,9 @@

S3method("[",fcwtr_scalogram)
S3method(as.data.frame,fcwtr_scalogram)
S3method(as.matrix,fcwtr_scalogram)
S3method(plot,fcwtr_scalogram)
S3method(print,fcwtr_scalogram)
export(fcwt)
export(fcwt_batch)
export(u)
Expand Down
6 changes: 4 additions & 2 deletions R/fcwt.R
Original file line number Diff line number Diff line change
Expand Up @@ -67,9 +67,11 @@
#'
#' @return
#' The spectogram, a numeric real-valued matrix with dimensions
#' `dim = c(length(signal), n_freqs)`.
#' `dim = c(length(signal), n_freqs)`, curated with some additional properties.
#' This matrix is wrapped into a S3-class `fcwtr_scalogram` so that plotting and
#' coercion functions can be used conveniently.
#' coercion functions can be used conveniently. Use `as.matrix()` to strip
#' the curated information. Or use `as.data.frame()` to convert to another
#' data format.
#'
#' @examples
#' ts_sin_440 <- sin((1:5000) * 2 * pi * 440 / 44100)
Expand Down
53 changes: 50 additions & 3 deletions R/fcwtr_scalogram.R
Original file line number Diff line number Diff line change
Expand Up @@ -218,14 +218,39 @@ tbind <- function(..., deparse.level = 1) {
)
}

#' Print the scalogram
#'
#' `print()` prints its argument and returns it invisibly (via `invisible(x)`).
#'
#' @param x The "fcwtr_scalogram" object resulting from [fcwt()] to print.
#' @inheritParams base::print
#'
#' @export
print.fcwtr_scalogram <- function(x, ...) {
cat("_Scalogram_\n")
cat("<> (Time/Frequency) dimension: [", sc_dim_time(x), ",",
sc_dim_freq(x), "]\n", sep = "")
cat("<> Sampling rate: ", format(attr(x, "sample_freq")), "\n", sep = "")
cat("<> Frequency scale: ", format(attr(x, "freq_begin")), " - ",
format(attr(x, "freq_end")), ", ", attr(x, "freq_scale"), "\n", sep = "")
cat("<> Time offset:", format(attr(x, "time_offset")), "\n")
cat("<> Sigma: ", attr(x, "sigma"), "\n", sep = "")

cat("Time/frequency matrix summary\n")
print(summary(as.matrix(x)))

invisible(x)
}


#' Coerce the scalogram matrix to a data frame
#'
#' Internally, the scalogram resulting from [fcwt()] is represented by
#' a numeric matrix. This method coerces this matrix into a reasonable
#' data frame. Note that this conversion has a significant run time cost.
#'
#' @param x
#' An object resulting from [fcwt()].
#' An "fcwtr_scalogram" object resulting from [fcwt()].
#'
#' @return
#' A [data.frame()] object representing the scalogram data with four columns:
Expand Down Expand Up @@ -267,8 +292,26 @@ as.data.frame.fcwtr_scalogram <- function(x, ...) {
)
}

#' Extract the data matrix from a scalogram
#'
#' Strips attributes and class from a scalogram object to retrieve
#' a pure matrix.
#'
#' @param x
#' An "fcwtr_scalogram" object resulting from [fcwt()].
#' @inheritParams base::as.matrix
#'
#' @export
as.matrix.fcwtr_scalogram <- function(x, ...) {
attributes(x) <- NULL

unclass(x)
}

#' Extract parts of a scalogram
#'
#' @param x
#' An "fcwtr_scalogram" object resulting from [fcwt()].
#' @param i,j
#' Indices corresponding to time slices of the spectogram which specify
#' elements to extract. Indices are numeric vectors or empty (missing)
Expand All @@ -285,6 +328,9 @@ as.data.frame.fcwtr_scalogram <- function(x, ...) {
#' elements corresponding to the sets of indices in each row of i.
#' An index value of NULL is treated as if it were integer(0).
#'
#' @return
#' Another "fcwtr_scalogram" object that contains only part of the data.
#'
#' @export
`[.fcwtr_scalogram` <- function(x, i, j) {
if (!missing(i)) {
Expand All @@ -309,7 +355,7 @@ as.data.frame.fcwtr_scalogram <- function(x, ...) {
#' Requires [ggplot2](https://ggplot2.tidyverse.org/).
#'
#' @param x
#' An object resulting from [fcwt()].
#' An "fcwtr_scalogram" object resulting from [fcwt()].
#'
#' @inheritParams autoplot.fcwtr_scalogram
#' @return No return value, called for side effects.
Expand Down Expand Up @@ -337,6 +383,8 @@ plot.fcwtr_scalogram <- function(x, n = 1000, time_unit = "s", freq_unit = "Hz",

#' Create a ggplot object resembling a scalogram
#'
#' @param object
#' A "fcwtr_scalogram" object resulting from [fcwt()].
#' @param n
#' The plotting function reduces the time resolution by averaging
#' to generate a reasonable graphics format. `n` is the number of time
Expand All @@ -355,7 +403,6 @@ plot.fcwtr_scalogram <- function(x, n = 1000, time_unit = "s", freq_unit = "Hz",
#' @return
#' A ggplot object.
#'
#' @keywords internal
autoplot.fcwtr_scalogram <- function(object, n = 1000,
time_unit = "s", freq_unit = "Hz", ...) {
stopifnot(requireNamespace("ggplot2", quietly = TRUE))
Expand Down
16 changes: 9 additions & 7 deletions _pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -7,16 +7,18 @@ reference:
Functions for performing fast continuous wavelet transforms.
contents:
- starts_with("fcwt")
- title: "Plotting"
desc: "Optional ggplot2 plotting methods (they only work if ggplot is installed)."
contents:
- plot.fcwtr_scalogram
- title: "Data frame conversion"
contents:
- as.data.frame.fcwtr_scalogram
- title: "Physical unit helper"
contents:
- u
- title: "Scalogram S3 methods"
desc: "A data.frame conversion method, data extractors, and optional ggplot2 plotting methods (they only work if ggplot is installed)."
contents:
- as.data.frame.fcwtr_scalogram
- as.matrix.fcwtr_scalogram
- "`[.fcwtr_scalogram`"
- print.fcwtr_scalogram
- plot.fcwtr_scalogram
- autoplot.fcwtr_scalogram
- title: "Sample data"
desc: >
Sample signal data mainly used to generate examples. The signals consist
Expand Down
2 changes: 1 addition & 1 deletion man/as.data.frame.fcwtr_scalogram.Rd

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

17 changes: 17 additions & 0 deletions man/as.matrix.fcwtr_scalogram.Rd

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

3 changes: 2 additions & 1 deletion man/autoplot.fcwtr_scalogram.Rd

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

6 changes: 4 additions & 2 deletions man/fcwt.Rd

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

2 changes: 1 addition & 1 deletion man/plot.fcwtr_scalogram.Rd

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

16 changes: 16 additions & 0 deletions man/print.fcwtr_scalogram.Rd

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

5 changes: 5 additions & 0 deletions man/sub-.fcwtr_scalogram.Rd

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

0 comments on commit 2942add

Please sign in to comment.