Skip to content

Commit

Permalink
Style, fix issue, build docs
Browse files Browse the repository at this point in the history
  • Loading branch information
pbulsink committed Oct 22, 2024
1 parent ecf70ed commit 3837f85
Show file tree
Hide file tree
Showing 9 changed files with 93 additions and 69 deletions.
3 changes: 2 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,8 @@ Suggests:
knitr,
rmarkdown,
ir,
ChemoSpec
ChemoSpec,
R.utils
Config/testthat/edition: 3
VignetteBuilder: knitr
BugReports: https://https://github.com/NRCan/PlotFTIR/issues
96 changes: 52 additions & 44 deletions R/io.R
Original file line number Diff line number Diff line change
Expand Up @@ -194,7 +194,7 @@ read_ftir_csv <- function(path, file, sample_name = NA, ...) {
}
}
if (!("absorbance" %in% colnames(input_file)) && !("transmittance" %in% colnames(input_file))) {
if (max(input_file[, colnames(input_file) != "wavenumber"]) > 10) {
if (max(input_file[, colnames(input_file) != "wavenumber"], na.rm = TRUE) > 10) {
# must be intensity = transmittance
cli::cli_inform("{.fn PlotFTIR:::read_ftir_csv} has deduced that input data column {.arg {colnames(input_file)[colnames(input_file) != 'wavenumber']}} is {.val transmittance}.")
colnames(input_file)[colnames(input_file) != "wavenumber"] <- "transmittance"
Expand Down Expand Up @@ -231,7 +231,7 @@ read_ftir_asp <- function(path, file, sample_name = NA, ...) {
"sample_id" = sample_name
)

if (max(ftir_data$intensity) > 10) {
if (max(ftir_data$intensity, na.rm = TRUE) > 10) {
# must be intensity = transmittance
cli::cli_inform("{.fn PlotFTIR:::read_ftir_spc} has deduced that input data is in {.val transmittance} units.")
colnames(ftir_data)[colnames(ftir_data) == "intensity"] <- "transmittance"
Expand Down Expand Up @@ -334,7 +334,7 @@ ir_to_plotftir <- function(ir_data, what = NA) {
# Package Checks
if (!requireNamespace("ir", quietly = TRUE)) {
cli::cli_abort(c("{.pkg PlotFTIR} requires {.pkg ir} package installation for this function.",
i = "Install {.pkg ir} with {.code install.packages('ir')}"
i = "Install {.pkg ir} with {.code install.packages('ir')}"
))
}

Expand All @@ -357,7 +357,7 @@ ir_to_plotftir <- function(ir_data, what = NA) {
}

if (all(is.numeric(what))) {
if (max(what) > nrow(ir_data) || min(what) < 1) {
if (max(what, na.rm = TRUE) > nrow(ir_data) || min(what) < 1) {
cli::cli_abort("Error in {.fn PlotFTIR::ir_to_plotftir}. {.arg what} must contain the row numbers of sample spectra to extract, or exact names matching what is in {.code ir_data$id_sample}.")
}
}
Expand All @@ -370,27 +370,26 @@ ir_to_df <- function(ir, what) {
# Internal function for ir_to_plotftir()
if (!requireNamespace("ir", quietly = TRUE)) {
cli::cli_abort(c("{.pkg PlotFTIR} requires {.pkg ir} package installation for this function.",
i = "Install {.pkg ir} with {.code install.packages('ir')}"
i = "Install {.pkg ir} with {.code install.packages('ir')}"
))
}

# Param checks

if (!("ir" %in% class(ir))) {
cli::cli_abort("Error in {.fn PlotFTIR::ir_to_df}. {.arg ir} must be of class {.cls ir}, produced by the {.pkg ir} package. You provided {.obj_type_friendly {ir}}.")
}

irdata <- ir::ir_get_spectrum(ir, what = what)
irdata <- mapply(cbind, irdata, "sample_id" = names(irdata), SIMPLIFY = F)
irdata <- dplyr::bind_rows(irdata) |>
dplyr::rename("wavenumber" = "x")
irdata <- mapply(cbind, irdata, "sample_id" = names(irdata), SIMPLIFY = FALSE)
irdata <- do.call(rbind, irdata)
colnames(irdata)[colnames(irdata)=='x'] <- "wavenumber"

intensity <- NA
ftir <- data.frame()
for (s in seq_along(unique(irdata$sample_id))) {
id <- unique(irdata$sample_id)[s]
sampleir <- irdata[irdata$sample_id == id, ]
if (max(sampleir$y) < 10) {
if (max(sampleir$y, na.rm = TRUE) < 10) {
sample_intensity <- "absorbance"
colnames(sampleir)[colnames(sampleir) == "y"] <- "absorbance"
} else {
Expand Down Expand Up @@ -454,13 +453,14 @@ ir_to_df <- function(ir, what) {
#' @examples
#' if (requireNamespace("ir", quietly = TRUE)) {
#' # convert biodiesel to a `ir` object
#' plotftir_to_ir(biodiesel, metadata = data.frame("Biodiesel_Content" = c(0, 0.25, 0.5, 1, 2.5, 5, 7.5, 10, 0.5, 5, NA)))
#' plotftir_to_ir(biodiesel,
#' metadata = data.frame("Biodiesel_Content" = c(0, 0.25, 0.5, 1, 2.5, 5, 7.5, 10, 0.5, 5, NA)))
#' }
plotftir_to_ir <- function(ftir, metadata = NA) {
# Package checks
if (!requireNamespace("ir", quietly = TRUE)) {
cli::cli_abort(c("{.pkg PlotFTIR} requires {.pkg ir} package installation for this function.",
i = "Install {.pkg ir} with {.code install.packages('ir')}"
i = "Install {.pkg ir} with {.code install.packages('ir')}"
))
}

Expand Down Expand Up @@ -514,7 +514,7 @@ plotftir_to_ir <- function(ftir, metadata = NA) {
#'
#' Un vecteur de chaînes de caractères. Correspond au paramètre `gr.crit` de [ChemoSpec::files2SpectraObject()].
#'
#' @param group_colors
#' @param group_colours
#' Group colours. Corresponds to [ChemoSpec::files2SpectraObject()] `gr.cols` parameter.
#'
#' Couleurs du groupe. Correspond au paramètre `gr.cols` de [ChemoSpec::files2SpectraObject()].
Expand All @@ -540,52 +540,59 @@ plotftir_to_ir <- function(ftir, metadata = NA) {
#' # convert biodiesel to a `chemospec` object
#' plotftir_to_chemospec(biodiesel)
#' }
plotftir_to_chemospec <- function(ftir, group_crit = NA, group_colours = "auto", description = "FTIR Study"){
plotftir_to_chemospec <- function(ftir, group_crit = NA, group_colours = "auto", description = "FTIR Study") {
# Package checks
if (!requireNamespace("ChemoSpec", quietly = TRUE)) {
cli::cli_abort(c("{.pkg PlotFTIR} requires {.pkg ChemoSpec} package installation for this function.",
i = "Install {.pkg ir} with {.code install.packages('ChemoSpec')}"
i = "Install {.pkg ChemoSpec} with {.code install.packages('ChemoSpec')}"
))
}
if (!requireNamespace("R.utils", quietly = TRUE)) {
cli::cli_abort(c("{.pkg PlotFTIR} and {.pkg ChemoSpec} requires {.pkg R.utils} package installation for this function.",
i = "Install {.pkg R.utils} with {.code install.packages('R.utils')}"
))
}

# Param Checks
ftir <- check_ftir_data(ftir, "PlotFTIR::plotftir_to_chemospec")

if (nchar(description) > 40){
if (nchar(description) > 40) {
cli::cli_alert_warning("{.pkg ChemoSpec} advises that {.param description} is 40 characters or less. Your description is {nchar(description)} characters.")
}

if(length(group_colours) == 1){
if(!group_colours %in% c('auto', 'Col7', 'Col8', 'Col12')){
if (length(group_colours) == 1) {
if (!group_colours %in% c("auto", "Col7", "Col8", "Col12")) {
cli::cli_abort("Error in {.fn PlotFTIR::plotftir_to_chemospec}. {.arg group_colours} must be one of {.code 'auto'}, {.code 'Col7'}, {.code 'Col8'}, {.code 'Col12'}, or a vector of the same length as {.param group_crit}.")
}
} else if (length(group_colours) != length(group_crit)){
} else if (length(group_colours) != length(group_crit)) {
cli::cli_abort("Error in {.fn PlotFTIR::plotftir_to_chemospec}. {.arg group_colours} must be one of {.code 'auto'}, {.code 'Col7'}, {.code 'Col8'}, {.code 'Col12'}, or a vector of the same length as {.param group_crit}.")
}

if(all(is.na(group_crit))){
if (all(is.na(group_crit))) {
group_crit <- unique(ftir$sample_id)
}

if(length(group_crit) > 8 && length(group_crit) <= 12 && length(group_colours) == 1){
if (length(group_crit) > 8 && length(group_crit) <= 12 && length(group_colours) == 1) {
cli::cli_alert_warning("Setting group_colours to {.code 'Col12'} to ensure enough colours available for groups.")
group_colours <- "Col12"
}

if(length(group_crit) > 12) {
if (length(group_crit) > 12) {
cli::cli_abort("Error in {.fn PlotFTIR::plotftir_to_chemospec}. {.arg group_crit} has to make 12 or less groups for {.pkg ChemoSpec} to be happy.")
}

intensity <- ifelse("absorbance" %in% colnames(ftir), "absorbance", "transmittance")
withr::with_dir(
tempdir(),{
for(i in seq_along(unique(ftir$sample_id))){
sid <- unique(ftir$sample_id)[i]
write.csv(ftir[ftir$sample_id == sid,], file = paste0("./",sid,".csv"))
}
cs_ftir <- ChemoSpec::files2SpectraObject(gr.crit = group_crit, gr.cols = group_colours, freq.unit = 'wavenumber',int.unit = intensity, fileExt = ".csv", descrip = description)
}
)
currentwd <- getwd()
dir<-tempdir()
setwd(dir)

for (i in seq_along(unique(ftir$sample_id))) {
sid <- unique(ftir$sample_id)[i]
utils::write.csv(ftir[ftir$sample_id == sid, c('wavenumber', intensity)], file = paste0("./", sid, ".csv"))
}
cs_ftir <- ChemoSpec::files2SpectraObject(gr.crit = group_crit, gr.cols = group_colours, freq.unit = "wavenumber", int.unit = intensity, fileExt = ".csv", descrip = description)

setwd(currentwd)

return(cs_ftir)
}
Expand Down Expand Up @@ -617,14 +624,14 @@ plotftir_to_chemospec <- function(ftir, group_crit = NA, group_colours = "auto",
#' @examples
#' if (requireNamespace("ChemoSpec", quietly = TRUE)) {
#' # convert `chemospec` to PlotFTIR data
#' SrE.IR <- data("SrE.IR", package = "ChemoSpec")
#' data("SrE.IR", package = "ChemoSpec", envir = environment())
#' chemospec_to_plotftir(SrE.IR)
#' }
chemospec_to_plotftir <- function(csdata){
chemospec_to_plotftir <- function(csdata) {
# Package checks
if (!requireNamespace("ChemoSpec", quietly = TRUE)) {
cli::cli_abort(c("{.pkg PlotFTIR} requires {.pkg ChemoSpec} package installation for this function.",
i = "Install {.pkg ir} with {.code install.packages('ChemoSpec')}"
i = "Install {.pkg ir} with {.code install.packages('ChemoSpec')}"
))
}

Expand All @@ -638,17 +645,19 @@ chemospec_to_plotftir <- function(csdata){

ftir <- data.frame()
allunits <- NA
for (i in seq_along(csdata$names)){
df <- data.frame("wavenumber" = csdata$freq,
"intensity" = csdata$data[i,],
"sample_id" = csdata$names[i])
sample_units <- ifelse(max(df$intensity, na.rm = T) > 10, "transmittance", "absorbance")
colnames(df)[colnames(df) == "intensity"]<-sample_units
if(is.na(allunits)){
for (i in seq_along(csdata$names)) {
df <- data.frame(
"wavenumber" = csdata$freq,
"intensity" = csdata$data[i, ],
"sample_id" = csdata$names[i]
)
sample_units <- ifelse(max(df$intensity, na.rm = TRUE) > 10, "transmittance", "absorbance")
colnames(df)[colnames(df) == "intensity"] <- sample_units
if (is.na(allunits)) {
all_units <- sample_units
}
if(all_units != sample_units){
if(all_units == "absorbance") {
if (all_units != sample_units) {
if (all_units == "absorbance") {
df <- transmittance_to_absorbance(df)
} else {
df <- absorbance_to_transmittance(df)
Expand All @@ -659,4 +668,3 @@ chemospec_to_plotftir <- function(csdata){

return(ftir)
}

4 changes: 2 additions & 2 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -143,12 +143,12 @@ get_plot_sample_ids <- function(ftir_spectra_plot) {
#' @return invisible ftir data if ok, typically called for effect of failure.
#' @keywords internal
check_ftir_data <- function(ftir, fn) {
if("ir" %in% class(ftir)){
if ("ir" %in% class(ftir)) {
cli::cli_inform("Converting {.pkg ir} data to {.pkg PlotFTIR} structure.")
ftir <- ir_to_plotftir(ftir)
}

if("Spectra" %in% class(ftir)){
if ("Spectra" %in% class(ftir)) {
cli::cli_inform("Converting {.pkg ChemoSpec} data to {.pkg PlotFTIR} structure.")
ftir <- chemospec_to_plotftir(ftir)
}
Expand Down
7 changes: 3 additions & 4 deletions README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -169,9 +169,9 @@ Functions are provided for adjusting the baseline of spectra, adding or subtract

`PlotFTIR` can read .csv and .asp file types. The .csv file should contain only one spectra, with columns for `wavenumber` and `absorbance` or `transmittance.` The .asp files should be according to the file specifications (not modified by the user).

## Interfacing With `ir` Package
## Interfacing With `ir` and `ChemoSpec` Packages

`PlotFTIR` has functions to interface with the `ir` package by Teickner. This package offers complex baseline capabilities, smoothing, and more data analysis tools. More information on the `ir` package is available in their [documetation (via CRAN)](https://cran.r-project.org/package=ir).
`PlotFTIR` has functions to interface with the `ir` package by Henning Teickner. This package offers complex baseline capabilities, smoothing, and more data analysis tools. More information on the `ir` package is available in their [documetation (via CRAN)](https://cran.r-project.org/package=ir). There is also capabilities to interface with `ChemoSpec` package by Bryan Hanson, which supports advanced statistics and chemometrics of spectral data. More information at [the `ChemoSpec` documentation](https://bryanhanson.github.io/ChemoSpec/index.html).

## Code of Conduct

Expand Down Expand Up @@ -333,13 +333,12 @@ Des fonctions sont fournies pour ajuster la ligne de base des spectres, ajouter

## Interfaçage avec le paquetage `ir`

`PlotFTIR` possède des fonctions pour s'interfacer avec le paquet `ir` de Teickner. Ce package offre des capacités de lignes de base complexes, de lissage, et plus d'outils d'analyse de données. Plus d'informations sur le paquet `ir` sont disponibles dans leur [documetation (via CRAN)] (https://cran.r-project.org/package=ir).
`PlotFTIR` possède des fonctions pour s'interfacer avec le paquet `ir` de Teickner. Ce package offre des capacités de lignes de base complexes, de lissage, et plus d'outils d'analyse de données. Plus d'informations sur le paquet `ir` sont disponibles dans leur [documetation (via CRAN)] (https://cran.r-project.org/package=ir). Il est également possible de s'interfacer avec le paquet `ChemoSpec` de Bryan Hanson, qui prend en charge les statistiques avancées et la chimiométrie des données spectrales. Plus d'informations sur [la documentation de `ChemoSpec`] (https://bryanhanson.github.io/ChemoSpec/index.html).

## Code de conduite

Veuillez noter que le projet `PlotFTIR` est publié avec un [Code de conduite pour le projet](CODE_OF_CONDUCT.md). En contribuant à ce projet, vous acceptez de respecter ces conditions.


## Citer ce paquet

Veuillez citer ce paquet dans tout article de journal contenant des images produites à l'aide de ce paquet. Si le paquet est installé à partir de GitHub ou de CRAN, le texte de la date sera correctement rempli avec l'année de publication.
Expand Down
24 changes: 16 additions & 8 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -221,13 +221,17 @@ contain only one spectra, with columns for `wavenumber` and `absorbance`
or `transmittance.` The .asp files should be according to the file
specifications (not modified by the user).

## Interfacing With `ir` Package

`PlotFTIR` has functions to interface with the `ir` package by Teickner.
This package offers complex baseline capabilities, smoothing, and more
data analysis tools. More information on the `ir` package is available
in their [documetation (via
CRAN)](https://cran.r-project.org/package=ir).
## Interfacing With `ir` and `ChemoSpec` Packages

`PlotFTIR` has functions to interface with the `ir` package by Henning
Teickner. This package offers complex baseline capabilities, smoothing,
and more data analysis tools. More information on the `ir` package is
available in their [documetation (via
CRAN)](https://cran.r-project.org/package=ir). There is also
capabilities to interface with `ChemoSpec` package by Bryan Hanson,
which supports advanced statistics and chemometrics of spectral data.
More information at [the `ChemoSpec`
documentation](https://bryanhanson.github.io/ChemoSpec/index.html).

## Code of Conduct

Expand Down Expand Up @@ -479,7 +483,11 @@ l’utilisateur).
de Teickner. Ce package offre des capacités de lignes de base complexes,
de lissage, et plus d’outils d’analyse de données. Plus d’informations
sur le paquet `ir` sont disponibles dans leur \[documetation (via
CRAN)\] (<https://cran.r-project.org/package=ir>).
CRAN)\] (<https://cran.r-project.org/package=ir>). Il est également
possible de s’interfacer avec le paquet `ChemoSpec` de Bryan Hanson, qui
prend en charge les statistiques avancées et la chimiométrie des données
spectrales. Plus d’informations sur \[la documentation de `ChemoSpec`\]
(<https://bryanhanson.github.io/ChemoSpec/index.html>).

## Code de conduite

Expand Down
2 changes: 1 addition & 1 deletion man/chemospec_to_plotftir.Rd

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

8 changes: 4 additions & 4 deletions man/plotftir_to_chemospec.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/plotftir_to_ir.Rd

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

15 changes: 11 additions & 4 deletions tests/testthat/test-io.R
Original file line number Diff line number Diff line change
Expand Up @@ -262,7 +262,14 @@ test_that("Interface to ChemoSpec is ok", {
if (!requireNamespace("ChemoSpec", quietly = TRUE)) {
expect_error(chemospec_to_plotftir(data.frame("testdata" = LETTERS)), regexp = "requires `ChemoSpec` package installation for this function.", fixed = TRUE)
expect_error(plotftir_to_chemospec(biodiesel), regexp = "requires `ChemoSpec` package installation for this function.", fixed = TRUE)
testthat::skip("ChemoSpec not available for testing interface")
}

if(!requireNamespace("R.utils", quietly = TRUE)) {
expect_error(plotftir_to_chemospec(biodiesel), regexp = "requires `R.utils` package installation for this function.", fixed = TRUE)
}

if(!requireNamespace("ChemoSpec", quietly = TRUE) || !requireNamespace("R.utils", quietly = TRUE)){
testthat::skip("ChemoSpec or R.utils not available for testing interface")
}

data("SrE.IR", package = "ChemoSpec", envir = environment())
Expand All @@ -277,14 +284,14 @@ test_that("Interface to ChemoSpec is ok", {
expect_equal(length(unique(csftir$sample_id)), length(SrE.IR$names))

expect_error(plotftir_to_chemospec(biodiesel, group_colours = "blue"), regexp = ", or a vector of the same length as group_crit", fixed = TRUE)
expect_error(plotftir_to_chemospec(biodiesel, group_crit = c('biodiesel', 'unknown'), group_colours = c("orange", "green", "blue")), regexp = ", or a vector of the same length as group_crit", fixed = TRUE)
expect_error(plotftir_to_chemospec(biodiesel, group_crit = c("biodiesel", "unknown"), group_colours = c("orange", "green", "blue")), regexp = ", or a vector of the same length as group_crit", fixed = TRUE)

expect_message(plotftir_to_chemospec(biodiesel), regexp = " to ensure enough colours available for groups.", fixed = TRUE)
expect_error(plotftir_to_chemospec(rbind(biodiesel, sample_spectra)), regexp = " has to make 12 or less groups for ChemoSpec to be happy", fixed = TRUE)

csdata <-plotftir_to_chemospec(biodiesel, group_crit = c('biodiesel', 'unknown'))
csdata <- plotftir_to_chemospec(biodiesel, group_crit = c("biodiesel", "unknown"))

expect_true(all(unique(biodiesel$sample_id) %in% csdata$names))
expect_equal(class(csdata), "Spectra")

expect_true("ggplot" %in% suppressWarnings(class(plot_ftir(SrE.IR))))
})

0 comments on commit 3837f85

Please sign in to comment.