- Add a column injectionTime to the data.frame returned by the header
function (all backends).
- Pwiz backend extracts the ion injection time.
- Update relevant documentation and add unit test(s).
... | ... |
@@ -91,7 +91,8 @@ setMethod("header", |
91 | 91 |
mergedScan=rep(-1, length(scans)), |
92 | 92 |
mergedResultScanNum=rep(-1, length(scans)), |
93 | 93 |
mergedResultStartScanNum=rep(-1, length(scans)), |
94 |
- mergedResultEndScanNum=rep(-1, length(scans))) |
|
94 |
+ mergedResultEndScanNum=rep(-1, length(scans)), |
|
95 |
+ injectionTime = rep(-1, length(scans))) |
|
95 | 96 |
|
96 | 97 |
return(result) |
97 | 98 |
}) |
... | ... |
@@ -40,15 +40,15 @@ test_header <- function() { |
40 | 40 |
cdf <- openMSfile(file, backend="netCDF") |
41 | 41 |
|
42 | 42 |
h <- header(cdf) |
43 |
- checkEquals(ncol(h), 19) |
|
43 |
+ checkEquals(ncol(h), 20) |
|
44 | 44 |
checkEquals(nrow(h), 1278) |
45 | 45 |
|
46 | 46 |
h <- header(cdf, 1) |
47 |
- checkEquals(ncol(h), 19) |
|
47 |
+ checkEquals(ncol(h), 20) |
|
48 | 48 |
checkEquals(nrow(h), 1) |
49 | 49 |
|
50 | 50 |
h <- header(cdf, 2:3) |
51 |
- checkEquals(ncol(h), 19) |
|
51 |
+ checkEquals(ncol(h), 20) |
|
52 | 52 |
checkEquals(nrow(h), 2) |
53 | 53 |
|
54 | 54 |
close(cdf) |
55 | 55 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,40 @@ |
1 |
+test_injection_time <- function() { |
|
2 |
+ library(msdata) |
|
3 |
+ library(mzR) |
|
4 |
+ library(RUnit) |
|
5 |
+ ## mzXML |
|
6 |
+ fl <- system.file("threonine", "threonine_i2_e35_pH_tree.mzXML", |
|
7 |
+ package = "msdata") |
|
8 |
+ mzxml <- openMSfile(fl, backend = "pwiz") |
|
9 |
+ hdr <- header(mzxml) |
|
10 |
+ mzR::close(mzxml) |
|
11 |
+ checkTrue(all(hdr$injectionTime == 0)) |
|
12 |
+ checkTrue(any(colnames(hdr) == "injectionTime")) |
|
13 |
+ fl <- system.file("threonine", "threonine_i2_e35_pH_tree.mzXML", |
|
14 |
+ package = "msdata") |
|
15 |
+ mzxml <- openMSfile(fl, backend = "Ramp") |
|
16 |
+ hdr <- header(mzxml) |
|
17 |
+ mzR::close(mzxml) |
|
18 |
+ checkTrue(all(hdr$injectionTime == 0)) |
|
19 |
+ checkTrue(any(colnames(hdr) == "injectionTime")) |
|
20 |
+ |
|
21 |
+ ## CDF |
|
22 |
+ fl <- system.file("cdf", "ko15.CDF", |
|
23 |
+ package = "msdata") |
|
24 |
+ mzxml <- openMSfile(fl, backend = "netCDF") |
|
25 |
+ hdr <- header(mzxml) |
|
26 |
+ mzR::close(mzxml) |
|
27 |
+ checkTrue(all(hdr$injectionTime == -1)) |
|
28 |
+ checkTrue(any(colnames(hdr) == "injectionTime")) |
|
29 |
+ |
|
30 |
+ ## mzML - with injection time present. |
|
31 |
+ fl <- system.file("proteomics", |
|
32 |
+ "TMT_Erwinia_1uLSike_Top10HCD_isol2_45stepped_60min_01.mzML.gz", |
|
33 |
+ package = "msdata") |
|
34 |
+ mzxml <- openMSfile(fl, backend = "pwiz") |
|
35 |
+ hdr <- header(mzxml) |
|
36 |
+ mzR::close(mzxml) |
|
37 |
+ checkTrue(all(hdr$injectionTime != 0)) |
|
38 |
+ checkTrue(any(colnames(hdr) == "injectionTime")) |
|
39 |
+ |
|
40 |
+} |
... | ... |
@@ -124,20 +124,23 @@ test_getScanHeaderInfo <- function() { |
124 | 124 |
## Read single scan header. |
125 | 125 |
scan_3 <- header(mzml, scans = 3) |
126 | 126 |
scan_3_ramp <- header(ramp, scans = 3) |
127 |
- ## Ramp does not read polarity |
|
127 |
+ ## Ramp does not read polarity or injectionTime |
|
128 | 128 |
scan_3$polarity <- 0 |
129 |
+ scan_3$injectionTime <- 0 |
|
129 | 130 |
checkEquals(scan_3, scan_3_ramp) |
130 | 131 |
|
131 | 132 |
## Read all scan header |
132 | 133 |
all_scans <- header(mzml) |
133 | 134 |
all_scans_ramp <- header(ramp) |
134 | 135 |
all_scans$polarity <- 0 |
136 |
+ all_scans$injectionTime <- 0 |
|
135 | 137 |
checkEquals(all_scans, all_scans_ramp) |
136 | 138 |
|
137 | 139 |
## passing the index of all scan headers should return the same |
138 | 140 |
all_scans_2 <- header(mzml, scans = 1:nrow(all_scans)) |
139 | 141 |
all_scans_ramp_2 <- header(ramp, scans = 1:nrow(all_scans)) |
140 | 142 |
all_scans_2$polarity <- 0 |
143 |
+ all_scans_2$injectionTime <- 0 |
|
141 | 144 |
checkEquals(all_scans, all_scans_2) |
142 | 145 |
checkEquals(as.list(all_scans[3, ]), scan_3) |
143 | 146 |
checkEquals(all_scans_2, all_scans_ramp_2) |
... | ... |
@@ -147,6 +150,7 @@ test_getScanHeaderInfo <- function() { |
147 | 150 |
scan_3_ramp <- header(ramp, scans = c(3, 1, 14)) |
148 | 151 |
## Ramp does not read polarity |
149 | 152 |
scan_3$polarity <- 0 |
153 |
+ scan_3$injectionTime <- 0 |
|
150 | 154 |
checkEquals(scan_3, scan_3_ramp) |
151 | 155 |
|
152 | 156 |
close(mzml) |
... | ... |
@@ -97,7 +97,8 @@ |
97 | 97 |
\code{precursorScanNum}, \code{precursorMZ}, \code{precursorCharge}, |
98 | 98 |
\code{precursorIntensity}, \code{mergedScan}, |
99 | 99 |
\code{mergedResultScanNum}, \code{mergedResultStartScanNum} and |
100 |
- \code{mergedResultEndScanNum}, when available in the original file. If |
|
100 |
+ \code{mergedResultEndScanNum}, \code{injectionTime} (ion injection |
|
101 |
+ time) when available in the original file. If |
|
101 | 102 |
multiple scans are queried, a \code{data.frame} is returned with the |
102 | 103 |
scans reported along the rows. |
103 | 104 |
|
... | ... |
@@ -186,6 +186,7 @@ Rcpp::DataFrame RcppPwiz::getScanHeaderInfo (Rcpp::IntegerVector whichScan) |
186 | 186 |
Rcpp::IntegerVector mergedResultScanNum(N_scans); /* scan number of the resultant merged scan */ |
187 | 187 |
Rcpp::IntegerVector mergedResultStartScanNum(N_scans); /* smallest scan number of the scanOrigin for merged scan */ |
188 | 188 |
Rcpp::IntegerVector mergedResultEndScanNum(N_scans); /* largest scan number of the scanOrigin for merged scan */ |
189 |
+ Rcpp::NumericVector ionInjectionTime(N_scans); /* The time spent filling an ion trapping device*/ |
|
189 | 190 |
|
190 | 191 |
for (int i = 0; i < N_scans; i++) |
191 | 192 |
{ |
... | ... |
@@ -196,9 +197,13 @@ Rcpp::DataFrame RcppPwiz::getScanHeaderInfo (Rcpp::IntegerVector whichScan) |
196 | 197 |
msLevel[i] = scanHeader.msLevel; |
197 | 198 |
|
198 | 199 |
SpectrumPtr sp = slp->spectrum(current_scan-1, false); // Is TRUE neccessary here ? |
200 |
+ Scan dummy; |
|
201 |
+ Scan& scan = sp->scanList.scans.empty() ? dummy : sp->scanList.scans[0]; |
|
199 | 202 |
CVParam param = sp->cvParamChild(MS_scan_polarity); |
200 | 203 |
polarity[i] = (param.cvid==MS_negative_scan ? 0 : (param.cvid==MS_positive_scan ? +1 : -1 ) ); |
201 |
- |
|
204 |
+ // ionInjectionTime[i] = sp->cvParam(MS_ion_injection_time).valueAs<double>(); |
|
205 |
+ ionInjectionTime[i] = scan.cvParam(MS_ion_injection_time).timeInSeconds(); |
|
206 |
+ |
|
202 | 207 |
peaksCount[i] = scanHeader.peaksCount; |
203 | 208 |
totIonCurrent[i] = scanHeader.totIonCurrent; |
204 | 209 |
retentionTime[i] = scanHeader.retentionTime; |
... | ... |
@@ -221,7 +226,7 @@ Rcpp::DataFrame RcppPwiz::getScanHeaderInfo (Rcpp::IntegerVector whichScan) |
221 | 226 |
delete adapter; |
222 | 227 |
adapter = NULL; |
223 | 228 |
|
224 |
- Rcpp::List header(21); |
|
229 |
+ Rcpp::List header(22); |
|
225 | 230 |
std::vector<std::string> names; |
226 | 231 |
int i = 0; |
227 | 232 |
names.push_back("seqNum"); |
... | ... |
@@ -266,6 +271,8 @@ Rcpp::DataFrame RcppPwiz::getScanHeaderInfo (Rcpp::IntegerVector whichScan) |
266 | 271 |
header[i++] = Rcpp::wrap(mergedResultStartScanNum); |
267 | 272 |
names.push_back("mergedResultEndScanNum"); |
268 | 273 |
header[i++] = Rcpp::wrap(mergedResultEndScanNum); |
274 |
+ names.push_back("injectionTime"); |
|
275 |
+ header[i++] = Rcpp::wrap(ionInjectionTime); |
|
269 | 276 |
|
270 | 277 |
header.attr("names") = names; |
271 | 278 |
|
... | ... |
@@ -148,7 +148,7 @@ Rcpp::List RcppRamp::getScanHeaderInfo ( int whichScan ) |
148 | 148 |
delete info; |
149 | 149 |
|
150 | 150 |
std::vector<std::string> names; |
151 |
- Rcpp::List header(21); |
|
151 |
+ Rcpp::List header(22); |
|
152 | 152 |
int i = 0; |
153 | 153 |
|
154 | 154 |
names.push_back("seqNum"); |
... | ... |
@@ -193,6 +193,8 @@ Rcpp::List RcppRamp::getScanHeaderInfo ( int whichScan ) |
193 | 193 |
header[i++] = Rcpp::wrap(data.mergedResultStartScanNum); |
194 | 194 |
names.push_back("mergedResultEndScanNum"); |
195 | 195 |
header[i++] = Rcpp::wrap(data.mergedResultEndScanNum); |
196 |
+ names.push_back("injectionTime"); |
|
197 |
+ header[i++] = 0; |
|
196 | 198 |
|
197 | 199 |
header.attr("names") = names; |
198 | 200 |
|
... | ... |
@@ -260,7 +262,7 @@ Rcpp::DataFrame RcppRamp::getAllScanHeaderInfo ( ) |
260 | 262 |
mergedResultEndScanNum[whichScan-1] = scanHeader.mergedResultEndScanNum; |
261 | 263 |
} |
262 | 264 |
|
263 |
- Rcpp::List header(21); |
|
265 |
+ Rcpp::List header(22); |
|
264 | 266 |
std::vector<std::string> names; |
265 | 267 |
int i = 0; |
266 | 268 |
|
... | ... |
@@ -306,6 +308,8 @@ Rcpp::DataFrame RcppRamp::getAllScanHeaderInfo ( ) |
306 | 308 |
header[i++] =Rcpp::wrap(mergedResultStartScanNum); |
307 | 309 |
names.push_back("mergedResultEndScanNum"); |
308 | 310 |
header[i++] =Rcpp::wrap(mergedResultEndScanNum); |
311 |
+ names.push_back("injectionTime"); |
|
312 |
+ header[i++] = 0; |
|
309 | 313 |
|
310 | 314 |
header.attr("names") = names; |
311 | 315 |
|