Skip to content

Commit

Permalink
ReadSpecClipboard extended to work also with connections (to facili…
Browse files Browse the repository at this point in the history
…tate testing on non windows platforms).

Snapshot testing for main function `InterpretMSSpectrum` implemented.
  • Loading branch information
janlisec committed Aug 1, 2023
1 parent 5f2298c commit 135f0b5
Show file tree
Hide file tree
Showing 5 changed files with 36 additions and 8 deletions.
15 changes: 8 additions & 7 deletions R/ReadSpecClipboard.R
@@ -1,5 +1,6 @@
#' @title ReadSpecClipboard.
#' @description Read a mass spectrum from the windows clipboard.
#' @param con A connection other than 'clipboard' can be provided.
#' @return A spectrum as two-column matrix.
#' @export
#' @examples
Expand All @@ -10,21 +11,21 @@
#' InterpretMSSpectrum::ReadSpecClipboard()
#' }
#' }
ReadSpecClipboard <- function() {
stopifnot(length(grep("Windows", utils::sessionInfo()$running))==1)
ReadSpecClipboard <- function(con = "clipboard") {
if (length(grep("Windows", utils::sessionInfo()$running))!=1 && con == "clipboard") return(NULL)
# source could be Excel (German/English) or DA directly
spec <- readLines("clipboard")
spec <- readLines(con = con)
spec <- gsub("\t", " ", spec) # replace Tabs
if (length(grep("[^[:digit:],/. ]", spec[1])) == 1) spec <- spec[-1] # strip header if present
spec <- gsub(",", ".", spec) # replace Colons
spec <- gsub(" +$", "", spec) # trim white space end
spec <- gsub("^ +", "", spec) # trim white space start
# convert to numeric matrix
spec <- as.matrix(
t(sapply(spec, function(x) {
as.numeric(strsplit(x, " ")[[1]])
}))
)
t(sapply(spec, function(x) {
as.numeric(strsplit(x, " ")[[1]])
}))
)
if (ncol(spec) >= 3) spec <- spec[, 2:3]
rownames(spec) <- 1:nrow(spec)
colnames(spec) <- c("mz", "int")
Expand Down
5 changes: 4 additions & 1 deletion man/ReadSpecClipboard.Rd

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

10 changes: 10 additions & 0 deletions tests/testthat/_snaps/InterpretMSSpectrum.md
@@ -0,0 +1,10 @@
# InterpretMSSpectrum works

Code
InterpretMSSpectrum::InterpretMSSpectrum(spec = inp, correct_peak = cp, met_db = mdb,
formula_db = fdb, silent = FALSE)
Warning <simpleWarning>
[RemoveEmptyFragments] No Fragments left after step GetRdisopResult
no non-missing arguments to max; returning -Inf
[RemoveEmptyFragments] No Fragments left after step RemoveByScore

4 changes: 4 additions & 0 deletions tests/testthat/test-InterpretMSSpectrum.R
Expand Up @@ -18,5 +18,9 @@ testthat::test_that(
inp <- InterpretMSSpectrum::esi_spectrum
out <- InterpretMSSpectrum::InterpretMSSpectrum(spec=inp, precursor = 263.0534, param = "ESIneg", dppm = 1, silent=TRUE)
testthat::expect_length(out, 6)

# test the main output as snapshot test
testthat::expect_snapshot(InterpretMSSpectrum::InterpretMSSpectrum(spec=inp, correct_peak=cp, met_db=mdb, formula_db=fdb, silent=FALSE))

}
)
10 changes: 10 additions & 0 deletions tests/testthat/test-ReadSpecClipboard.R
@@ -0,0 +1,10 @@
testthat::test_that(
desc = "ReadSpecClipboard works as expected",
code = {
fn <- tempfile(fileext = ".txt")
x <- as.matrix(InterpretMSSpectrum::apci_spectrum)
rownames(x) <- 1:nrow(x)
write.table(x = x, file = fn, row.names = FALSE)
testthat::expect_equal(InterpretMSSpectrum::ReadSpecClipboard(con = fn), x)
}
)

0 comments on commit 135f0b5

Please sign in to comment.