Skip to content

Commit

Permalink
rewrite unit test according to template #55
Browse files Browse the repository at this point in the history
  • Loading branch information
Sang T. Truong committed Aug 10, 2021
1 parent 00103aa commit 0059230
Showing 1 changed file with 65 additions and 6 deletions.
71 changes: 65 additions & 6 deletions R/read_txt_Renishaw.R
Original file line number Diff line number Diff line change
Expand Up @@ -229,16 +229,75 @@ read_zip_Renishaw <- function(file = stop("filename is required"),
}


# Unit tests -----------------------------------------------------------------

# hySpc.testthat::test(read_zip_Renishaw) <- function() {
# context("read_zip_Renishaw")
# path <- system.file("extdata", "txt.Renishaw", package = "hySpc.read.txt")
# test_that("compressed files", {
#
# expect_equal(
# dim(read_zip_Renishaw(paste0(path, "/chondro.zip"))),
# c(nrow = 875L, ncol = 4L, nwl = 1272L)
# )
# })
# }


# Unit tests -----------------------------------------------------------------

hySpc.testthat::test(read_zip_Renishaw) <- function() {
context("read_zip_Renishaw")
local_edition(3)

path <- system.file("extdata", "txt.Renishaw", package = "hySpc.read.txt")
test_that("compressed files", {
f_chondro <- paste0(path, "/chondro.zip")
expect_silent(spc <- read_zip_Renishaw(f_paracetamol))

expect_equal(
dim(read_zip_Renishaw(paste0(path, "/chondro.zip"))),
c(nrow = 875L, ncol = 4L, nwl = 1272L)
)
n_wl <- nwl(spc)
n_rows <- nrow(spc)
n_clos <- ncol(spc)

test_that("Renishaw .zip: hyperSpec obj. dimensions are correct", {
expect_equal(n_wl, 1272)
expect_equal(n_rows, 875)
expect_equal(n_clos, 4)

})

test_that("Renishaw .zip: extra data are correct", {
# @data colnames
expect_equal(colnames(spc), c("y", "x", "spc", "filename"))

# @data values
# (Add tests, if relevant or remove this row)

})

test_that("Renishaw .zip: labels are correct", {
expect_equal(spc@label$.wavelength, expression(Delta * tilde(nu)/cm^-1))
expect_equal(spc@label$spc, expression("I / a.u."))
expect_equal(spc@label$filename, "filename")
})

test_that("Renishaw .txt: spectra are correct", {
# Dimensions of spectra matrix (@data$spc)
expect_equal(dim(spc@data$spc), c(875, 1272))

# Column names of spectra matrix
expect_equal(colnames(spc@data$spc)[1], "601.622")
expect_equal(colnames(spc@data$spc)[10], "610.989")
expect_equal(colnames(spc@data$spc)[n_wl], "1802.15") # last name

# Values of spectra matrix
expect_equal(unname(spc@data$spc[1, 1]), 501.723)
expect_equal(unname(spc@data$spc[1, 10]), 444.748)
expect_equal(unname(spc@data$spc[n_rows, n_wl]), 151.921) # last spc value

})

test_that("Renishaw .txt: wavelengths are correct", {
expect_equal(spc@wavelength[1], 601.622)
expect_equal(spc@wavelength[10], 610.989)
expect_equal(spc@wavelength[n_wl], 1802.15)
})
}

0 comments on commit 0059230

Please sign in to comment.