Skip to content

Commit

Permalink
#4
Browse files Browse the repository at this point in the history
  • Loading branch information
cpanse committed Sep 8, 2020
1 parent 947fde0 commit f0a527b
Showing 1 changed file with 99 additions and 8 deletions.
107 changes: 99 additions & 8 deletions R/rawR.R
Original file line number Diff line number Diff line change
@@ -1,17 +1,23 @@
#' readSpectrum of a raw file
#' Read a Set of Spectra
#'
#' @param rawfile the name of the Thermo Fisher Scietific raw file which
#' the data are to be read from.
#' @param rawfile the name of the Thermo Fisher Scietific raw file.
#' @param scans a vector of requested scan numbers.
#' @param tmpdir a non-empty character vector giving the directory name; default
#' uses \code{tempdir()}.
#' @author Christian Panse <[email protected]> 2018, 2019, 2020
#' @author Tobias Kockmann and Christian Panse <[email protected]> 2018, 2019, 2020
#'
#' @description the function reads scan information of a given set of scan
#' number using a dot net interface and the ThermoFisher NewRawFileReader
#' libraries.
#' @description the function reads scan information, e.g., charge, mZ,
#' or intensity of a given set of scan numbers using a dot net interface and
#' the ThermoFisher NewRawFileReader libraries.
#'
#' @references \url{https://doi.org/10.5281/zenodo.2640013}
#' @seealso Thermo Fisher NewRawfileReader C# code snippets
#' \url{https://planetorbitrap.com/rawfilereader}.
#'
#' @references \itemize{
#' \item{\url{https://doi.org/10.5281/zenodo.2640013}}
#' \item{the R function 1st appeared in
#' \url{https://doi.org/10.1021/acs.jproteome.8b00173}}
#' }
#'
#' @aliases readSpectrum
#'
Expand All @@ -26,11 +32,25 @@
#' S <- readSpectrum(rawfile, scans = 1:9)
#'
#' S[[1]]
#'
#' names(S[[1]])
#'
#' .plot.peaklist <- function(x, ...){
#' plot(x$mZ, x$intensity, type='h')
#' labels <- na.omit(lapply(x, function(y){if (length(y)==1){y}else{NA}}))
#' legend("topright", paste(names(labels), labels, sep=": "), ...)
#' }
#'
readSpectrum <- function(rawfile, scans, tmpdir=tempdir()){
mono <- if(Sys.info()['sysname'] %in% c("Darwin", "Linux")) TRUE else FALSE
exe <- file.path(path.package(package = "rawR"), "exec", "rawR.exe")


if (!file.exists(rawfile)){
warning('file not available. return.')
return
}

tfi <- tempfile(tmpdir=tmpdir)
tfo <- tempfile(tmpdir=tmpdir)
tfstdout <- tempfile(tmpdir=tmpdir)
Expand All @@ -54,3 +74,74 @@ readSpectrum <- function(rawfile, scans, tmpdir=tempdir()){
return(lapply(e$PeakList,
function(x){class(x) <- c(class(x), 'peaklist'); x}))
}


#' read file header Information
#'
#' @param rawfile the name of the Thermo Fisher Scietific raw file
#' @param mono enviroment
#' @param exe path of the executable.
#' @param mono_path default.
#' @param argv arguments, default.
#' @param system2_call system2 call, default.
#' @param method instrument vendor
#' @description The function extracts some meta information from a given rawfile.
#' The R code output is parsed by the function and a list object is returned.
#' @author Tobias Kockmann and Christian Panse 2018, 2019, 2020
#' @seealso Thermo Fisher NewRawfileReader C# code snippets
#' \url{https://planetorbitrap.com/rawfilereader}.
#'
#' @return a list object
#' @export readFileHeader
#'
#' @examples
#' (rawfile <- file.path(path.package(package = 'rawR'), 'extdata',
#' 'sample.raw'))
#'
#' M <- readFileHeader(rawfile)
readFileHeader <- function(rawfile,
mono = if(Sys.info()['sysname'] %in% c("Darwin", "Linux")) TRUE else FALSE,
exe = file.path(path.package(package = "rawR"), "exec", "rawR.exe"),
mono_path = "",
argv = "infoR",
system2_call = TRUE,
method = "thermo"){

if (!file.exists(rawfile)){
warning('file not available. return.')
return
}
if(system2_call && method == 'thermo'){

tf <- tempfile(fileext = '.R')
tf.err <- tempfile(fileext = '.err')

# message(paste("system2 is writting to tempfile ", tf, "..."))

if (mono){
rvs <- system2("mono", args = c(exe, shQuote(rawfile
), argv),
stdout = tf)
}else{
rvs <- system2(exe, args = c(shQuote(rawfile
), argv),
stderr = tf.err,
stdout = tf)
}

if (rvs == 0){

try({
source(tf)

#message(paste("unlinking", tf, "..."))
#unlink(tf)
return(e$info)
}, NULL)

# unlink(tfstdout)
return(rv)
}
}
NULL
}

0 comments on commit f0a527b

Please sign in to comment.