Skip to content

Commit

Permalink
CI: add tests for Shimadzu tables
Browse files Browse the repository at this point in the history
  • Loading branch information
ethanbass committed Dec 21, 2024
1 parent da2447a commit fa98638
Show file tree
Hide file tree
Showing 3 changed files with 88 additions and 6 deletions.
4 changes: 2 additions & 2 deletions R/read_peaklist.R
Original file line number Diff line number Diff line change
Expand Up @@ -106,10 +106,10 @@ read_peaklist <- function(paths, find_files,
data <- lapply(seq_along(data), function(i){
if (inherits(data[[i]], "list")){
lapply(data[[i]], function(xx){
cbind(Sample = file_names[i], xx)
cbind(sample = file_names[i], xx)
})
} else {
cbind(Sample = file_names[i], data[[i]])
cbind(sample = file_names[i], data[[i]])
}
})
class(data) <- "peak_list"
Expand Down
82 changes: 82 additions & 0 deletions tests/testthat/test-extra.R
Original file line number Diff line number Diff line change
Expand Up @@ -592,6 +592,38 @@ test_that("read_chroms can read 'Shimadzu' PDA files (ASCII and LCD)", {
round(attr(x2, "time_range"), 3))
})

test_that("Shimadzu Anthocyanin peak tables match", {
skip_on_cran()
skip_if_not_installed("chromConverterExtraTests")

path_ascii <- system.file("shimadzuDAD_Anthocyanin.txt",
package = "chromConverterExtraTests")
skip_if_not(file.exists(path_ascii))

path_lcd <- system.file("Anthocyanin.lcd",
package = "chromConverterExtraTests")
skip_if_not(file.exists(path_lcd))

x <- read_peaklist(path_ascii, format_in = "shimadzu_dad",
data_format = "original",
progress_bar = FALSE)[[1]]

x1 <- read_shimadzu_lcd(path_lcd, what="peak_table")
x1 <- read_peaklist(path_lcd, format_in = "shimadzu_lcd", progress_bar=FALSE)[[1]]

expect_equal(x[[1]][,c(3,6:7,4:5,8:9,11,13:18,21:22)],x1[[1]][,-1], tolerance=.001,
ignore_attr=TRUE)
expect_equal(x[[2]][,c(3,6:7,4:5,8:9,11,13:18,21:22)],x1[[3]][,-1], tolerance=.001,
ignore_attr=TRUE)
expect_equal(x[[3]][,c(3,6:7,4:5,8:9,11,13:18,21:22)],x1[[4]][,-1], tolerance=.001,
ignore_attr=TRUE)
expect_equal(x[[4]][,c(3,6:7,4:5,8:9,11,13:18,21:22)],x1[[5]][,-1], tolerance=.001,
ignore_attr=TRUE)
expect_equal(x[[5]][,c(3,6:7,4:5,8:9,11,13:18,21:22)],x1[[6]][,-1], tolerance=.001,
ignore_attr=TRUE)
})


test_that("read_chroms can read 2D chromatograms from 'Shimadzu' LCD files", {
skip_on_cran()
skip_if_not_installed("chromConverterExtraTests")
Expand Down Expand Up @@ -729,6 +761,36 @@ test_that("read_chroms can read multi-channel chromatograms from 'Shimadzu' LCD
expect_equal(x2[x2$lambda == "", "intensity"], x[["B"]], ignore_attr = TRUE)
})

test_that("Shimadzu multichannel peak tables match", {
skip_on_cran()
skip_if_not_installed("chromConverterExtraTests")

path_asc <- system.file("multichannel_chrom.txt",
package = "chromConverterExtraTests")

skip_if_not(file.exists(path_asc))

path_lcd <- system.file("multichannel_chrom.lcd",
package = "chromConverterExtraTests")
skip_if_not(file.exists(path_lcd))

x <- read_peaklist(path_asc, format_in = "shimadzu_dad",
data_format = "original",
progress_bar = FALSE)[[1]]

x1 <- read_peaklist(path_lcd, format_in = "shimadzu_lcd",
progress_bar=FALSE)[[1]]


expect_equal(x[[1]][,c(3,6:7,4:5,8:9,11,13:18,21:22)],x1[[1]][,-1], tolerance=.01,
ignore_attr=TRUE)
expect_equal(x[[2]][,c(3,6:7,4:5,8:9,11,13:18,21:22)],x1[[2]][,-1], tolerance=.001,
ignore_attr=TRUE)
expect_equal(x[[3]][,c(3,6:7,4:5,8:9,11,13:18,21:22)],x1[[3]][,-1], tolerance=.001,
ignore_attr=TRUE)
})


test_that("read_chroms can read 'Agilent' .dx files", {
skip_on_cran()
skip_if_not_installed("chromConverterExtraTests")
Expand Down Expand Up @@ -874,6 +936,26 @@ test_that("Shimadzu GCD parser works", {
expect_equal(as.numeric(attr(txt, "time_range")), round(attr(x, "time_range"), 3))
})

test_that("Shimadzu FID peak tables match", {
skip_on_cran()
skip_if_not_installed("chromConverterExtraTests")

path_asc <- test_path("testdata/ladder.txt")

path_gcd <- system.file("FS19_214.gcd", package = "chromConverterExtraTests")
skip_if_not(file.exists(path_gcd))

x <- read_peaklist(path_asc, format_in = "shimadzu_dad",
data_format = "original",
progress_bar = FALSE)[[1]]

x1 <- read_peaklist(path_gcd, format_in = "shimadzu_gcd", progress_bar=FALSE)

expect_equal(x[,c(3,6:7,4:5,8:9,11,13:18,21:22)], x1[[1]][,-1], tolerance=.001,
ignore_attr=TRUE)
})


test_that("Shimadzu QGD parser works", {
skip_on_cran()
skip_if_missing_dependencies()
Expand Down
8 changes: 4 additions & 4 deletions tests/testthat/test-read_chroms.R
Original file line number Diff line number Diff line change
Expand Up @@ -298,10 +298,10 @@ test_that("read_peaklist can read `Shimadzu` fid files", {
expect_equal(x[[1]][[1,"sample"]], "ladder")
expect_equal(x[[1]][[1,"sample"]], "ladder")
expect_equal(colnames(x[[1]]),
c("sample","Peak.","R.Time","I.Time","F.Time","Area","Height",
"A.H","Conc.","Mark","ID.","Name", "k.", "Plate..", "Plate.Ht.",
"Tailing", "Resolution", "Sep.Factor", "Area.Ratio", "Height.Ratio",
"Conc...", "Norm.Conc."))
c("sample","Peak#","R.Time","I.Time","F.Time","Area","Height",
"A/H","Conc.","Mark","ID#","Name", "k'", "Plate #", "Plate Ht.",
"Tailing", "Resolution", "Sep.Factor", "Area Ratio", "Height Ratio",
"Conc. %", "Norm Conc."))
expect_equal(attr(x, "class"), "peak_list")
})

0 comments on commit fa98638

Please sign in to comment.