Browse code

Extract run start time stamp (issue #66)

- Add related unit tests and documentation.

jotsetung authored on 03/08/2017 04:29:28
Showing 3 changed files

... ...
@@ -1,6 +1,7 @@
1 1
 CHANGES IN VERSION 2.11.6
2 2
 -------------------------
3
- o Nothing yet
3
+ o runInfo returns the run start time stamp from files providing this
4
+   information (mzML files).
4 5
  
5 6
 CHANGES IN VERSION 2.11.5
6 7
 -------------------------
7 8
new file mode 100644
... ...
@@ -0,0 +1,56 @@
1
+test_runStartTimeStamp_pwiz <- function() {
2
+    ## Works on (some) mzML, what with mzXML?
3
+    library(msdata)
4
+    library(mzR)
5
+    f <- system.file("lockmass/LockMass_test.mzXML", package = "msdata")
6
+    fh <- mzR::openMSfile(f)
7
+    run_info <- runInfo(fh)
8
+    checkTrue(any(names(run_info) == "startTimeStamp"))
9
+    checkTrue(is.na(run_info$startTimeStamp))
10
+    mzR::close(fh)
11
+    
12
+    f <- system.file("microtofq/MM14.mzML", package = "msdata")
13
+    fh <- mzR::openMSfile(f)
14
+    run_info <- runInfo(fh)
15
+    checkTrue(any(names(run_info) == "startTimeStamp"))
16
+    checkTrue(is.na(run_info$startTimeStamp))
17
+    mzR::close(fh)
18
+    
19
+    f <- system.file("microtofq/MM8.mzML", package = "msdata")
20
+    fh <- mzR::openMSfile(f)
21
+    run_info <- runInfo(fh)
22
+    checkTrue(any(names(run_info) == "startTimeStamp"))
23
+    checkTrue(!is.na(run_info$startTimeStamp))
24
+    checkTrue(is.character(run_info$startTimeStamp))
25
+    mzR::close(fh)
26
+    
27
+    f <- system.file("proteomics/TMT_Erwinia_1uLSike_Top10HCD_isol2_45stepped_60min_01.mzML.gz", package = "msdata")
28
+    fh <- mzR::openMSfile(f)
29
+    run_info <- runInfo(fh)
30
+    checkTrue(any(names(run_info) == "startTimeStamp"))
31
+    checkTrue(!is.na(run_info$startTimeStamp))
32
+    checkTrue(is.character(run_info$startTimeStamp))
33
+    mzR::close(fh)
34
+}
35
+
36
+test_runStartTimeStamp_cdf <- function() {
37
+    ## Can not extract from CDF
38
+    f <- system.file("cdf/ko15.CDF", package = "msdata")
39
+    fh <- mzR::openMSfile(f, backend = "netCDF")
40
+    run_info <- runInfo(fh)
41
+    checkTrue(any(names(run_info) == "startTimeStamp"))
42
+    checkTrue(is.na(run_info$startTimeStamp))
43
+    mzR::close(fh)
44
+}
45
+
46
+test_runStartTimeStamp_ramp <- function() {
47
+    ## Can not extract from ramp
48
+    f <- system.file("iontrap/extracted.mzData", package = "msdata")
49
+    fh <- mzR::openMSfile(f, backend = "Ramp")
50
+    run_info <- runInfo(fh)
51
+    checkTrue(any(names(run_info) == "startTimeStamp"))
52
+    checkTrue(is.na(run_info$startTimeStamp))
53
+    mzR::close(fh)
54
+}
55
+
56
+
... ...
@@ -55,7 +55,10 @@ para(object)
55 55
   Accessors to the analytical setup metadata of a run.
56 56
   \code{runInfo} will show a summary of the experiment as a named list,
57 57
   including \code{scanCount}, \code{lowMZ}, \code{highMZ},
58
-  \code{dStartTime} and \code{dEndTime}.
58
+  \code{dStartTime}, \code{dEndTime} and \code{startTimeStamp}. Note
59
+  that \code{startTimeStamp} can only be extracted from \emph{mzML}
60
+  files using the \emph{pwiz} backend. A \code{NA} is reported if its
61
+  value is not available.
59 62
   The \code{instrumentInfo} method returns a named \code{list} including
60 63
   instrument manufacturer, model, ionisation technique, analyzer and
61 64
   detector. \code{mzRpwiz} will give more additional information including