Browse code

Merge pull request #165 from jotsetung/hasChromatograms

Add .hasChromatograms function (issue #164)

Laurent Gatto authored on 16/05/2018 13:36:26 • GitHub committed on 16/05/2018 13:36:26
Showing 8 changed files

... ...
@@ -169,3 +169,13 @@ setMethod("show",
169 169
             invisible(NULL)
170 170
           })
171 171
 
172
+setMethod("chromatograms", "mzRnetCDF", function(object, chrom)
173
+    chromatogram(object, chrom))
174
+setMethod("chromatogram", "mzRnetCDF", function(object, chrom) {
175
+    warning("The mzRnetCdf backend does not support chromatographic data")
176
+    .empty_chromatogram()
177
+})
178
+setMethod("chromatogramHeader", "mzRnetCDF", function(object, chrom) {
179
+    warning("The mzRnetCdf backend does not support chromatographic data")
180
+    .empty_chromatogram_header()
181
+})
... ...
@@ -163,3 +163,14 @@ setMethod("show",
163 163
 
164 164
 setMethod("isolationWindow", "mzRramp",
165 165
           function(object, ...) .isolationWindow(fileName(object), ...))
166
+
167
+setMethod("chromatograms", "mzRramp", function(object, chrom)
168
+    chromatogram(object, chrom))
169
+setMethod("chromatogram", "mzRramp", function(object, chrom) {
170
+    warning("The mzRnetCdf backend does not support chromatographic data")
171
+    .empty_chromatogram()
172
+})
173
+setMethod("chromatogramHeader", "mzRramp", function(object, chrom) {
174
+    warning("The mzRnetCdf backend does not support chromatographic data")
175
+    .empty_chromatogram_header()
176
+})
... ...
@@ -43,8 +43,56 @@ setMethod("isolationWindow", "character",
43 43
 
44 44
 
45 45
 .hasSpectra <- function(x) {
46
-    if (is.character(x) & file.exists(x))
46
+    close_after <- FALSE
47
+    if (is.character(x) && file.exists(x)) {
47 48
         x <- mzR::openMSfile(x)
49
+        ## Ensure we are closing the file later
50
+        close_after <- TRUE
51
+    }
52
+    stopifnot(inherits(x, "mzR"))
53
+    len <- length(x)
54
+    if (close_after)
55
+        close(x)
56
+    return(as.logical(len))
57
+}
58
+
59
+#' Create return data for MS backends not supporting chromatographic data. This
60
+#' function is supposed to be called by the chromatogram(s) methods for these
61
+#' backends
62
+#'
63
+#' @author Johannes Rainer
64
+#'
65
+#' @noRd
66
+.empty_chromatogram <- function() {
67
+    list()
68
+}
69
+
70
+#' Create return data for MS backends not supporting chromatographic data.
71
+#'
72
+#' @author Johannes Rainer
73
+#'
74
+#' @noRd
75
+.empty_chromatogram_header <- function() {
76
+    cn <- c("chromatogramId", "chromatogramIndex", "polarity",
77
+            "precursorIsolationWindowTargetMZ",
78
+            "precursorIsolationWindowLowerOffset",
79
+            "precursorIsolationWindowUpperOffset",
80
+            "precursorCollisionEnergy", "productIsolationWindowTargetMZ",
81
+            "productIsolationWindowLowerOffset",
82
+            "productIsolationWindowUpperOffset")
83
+    data.frame(matrix(nrow = 0, ncol = length(cn),
84
+                      dimnames = list(character(), cn)))
85
+}
86
+
87
+.hasChromatograms <- function(x) {
88
+    close_after <- FALSE
89
+    if (is.character(x) && file.exists(x)) {
90
+        x <- mzR::openMSfile(x)
91
+        close_after <- TRUE
92
+    }
48 93
     stopifnot(inherits(x, "mzR"))
49
-    return(as.logical(length(x)))
94
+    hdr <- chromatogramHeader(x)
95
+    if (close_after)
96
+        close(x)
97
+    as.logical(nrow(hdr))
50 98
 }
... ...
@@ -58,3 +58,27 @@ test_header <- function() {
58 58
 
59 59
   close(cdf)
60 60
 }
61
+
62
+test_chromatogram <- function() {
63
+    file <- system.file('cdf/ko15.CDF', package = "msdata")
64
+    x <- openMSfile(file, backend="netCDF")        
65
+    suppressWarnings(
66
+        chr <- chromatogram(x)
67
+    )
68
+    checkTrue(length(chr) == 0)
69
+    suppressWarnings(
70
+        chr <- chromatograms(x)
71
+    )
72
+    checkTrue(length(chr) == 0)
73
+    close(x)
74
+}
75
+
76
+test_chromatogramHeader <- function() {
77
+    file <- system.file('cdf/ko15.CDF', package = "msdata")
78
+    x <- openMSfile(file, backend="netCDF")        
79
+    suppressWarnings(
80
+        ch <- chromatogramHeader(x)
81
+    )
82
+    checkTrue(nrow(ch) == 0)
83
+    close(x)
84
+}
... ...
@@ -102,4 +102,32 @@ test_peaks_spectra <- function() {
102 102
     p <- peaks(x, 1:10)
103 103
     s <- spectra(x, 1:10)
104 104
     checkIdentical(p, s)
105
+    close(x)
105 106
 }
107
+
108
+test_chromatogram <- function() {
109
+    library("msdata")
110
+    f <- proteomics(full.names = TRUE)
111
+    x <- openMSfile(f[1], backend = "Ramp")
112
+    suppressWarnings(
113
+        chr <- chromatogram(x)
114
+    )
115
+    checkTrue(length(chr) == 0)
116
+    suppressWarnings(
117
+        chr <- chromatograms(x)
118
+    )
119
+    checkTrue(length(chr) == 0)
120
+    close(x)
121
+}
122
+
123
+test_chromatogramHeader <- function() {
124
+    library("msdata")
125
+    f <- proteomics(full.names = TRUE)
126
+    x <- openMSfile(f[1], backend = "Ramp")
127
+    suppressWarnings(
128
+        ch <- chromatogramHeader(x)
129
+    )
130
+    checkTrue(nrow(ch) == 0)
131
+    close(x)
132
+}
133
+
106 134
new file mode 100644
... ...
@@ -0,0 +1,20 @@
1
+test_hasChromatograms <- function() {
2
+    fl <- system.file("proteomics/MRM-standmix-5.mzML.gz", package = "msdata")
3
+    x <- mzR::openMSfile(fl, backend = "pwiz")
4
+    checkTrue(mzR:::.hasChromatograms(x))
5
+    checkTrue(mzR:::.hasChromatograms(fl))
6
+    close(x)
7
+    
8
+    fl <- system.file("cdf/ko15.CDF", package = "msdata")
9
+    x <- openMSfile(fl, backend = "netCDF")        
10
+    suppressWarnings(checkTrue(!mzR:::.hasChromatograms(x)))
11
+    suppressWarnings(checkTrue(!mzR:::.hasChromatograms(fl)))
12
+    close(x)
13
+
14
+    fl <- system.file("sciex/20171016_POOL_POS_1_105-134.mzML",
15
+                      package = "msdata")
16
+    x <- mzR::openMSfile(fl, backend = "pwiz")
17
+    checkTrue(!mzR:::.hasChromatograms(x))
18
+    checkTrue(!mzR:::.hasChromatograms(fl))
19
+    close(x)
20
+}
... ...
@@ -29,6 +29,12 @@
29 29
 \alias{chromatogram,mzRpwiz-method}
30 30
 \alias{chromatogramHeader,mzRpwiz-method}
31 31
 \alias{chromatograms,mzRpwiz-method}
32
+\alias{chromatogram,mzRramp-method}
33
+\alias{chromatogramHeader,mzRramp-method}
34
+\alias{chromatograms,mzRramp-method}
35
+\alias{chromatogram,mzRnetCDF-method}
36
+\alias{chromatogramHeader,mzRnetCDF-method}
37
+\alias{chromatograms,mzRnetCDF-method}
32 38
 \alias{tic,mzRpwiz-method}
33 39
 \alias{nChrom}
34 40
 \alias{chromatogram}
... ...
@@ -885,10 +885,11 @@ Rcpp::DataFrame RcppPwiz::getAllChromatogramHeaderInfo ( ) {
885 885
   if (msd != NULL) {
886 886
     ChromatogramListPtr clp = msd->run.chromatogramListPtr;
887 887
     int N = clp->size();
888
-    
889
-    return getChromatogramHeaderInfo(Rcpp::seq(1, N));
888
+    if (N > 0)
889
+      return getChromatogramHeaderInfo(Rcpp::seq(1, N));
890
+  } else {
891
+    Rprintf("Warning: pwiz not yet initialized.\n ");
890 892
   }
891
-  Rprintf("Warning: pwiz not yet initialized.\n ");
892 893
   return Rcpp::DataFrame::create( );
893 894
 }
894 895