Browse code

back-ported the old XCMS rampR interface, which is much faster than cramp

git-svn-id: https://hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/mzR@63802 bc3139a8-67e5-0310-9ffc-ced21a209358

s.neumann authored on 13/03/2012 11:40:20
Showing 2 changed files

1 1
new file mode 100644
... ...
@@ -0,0 +1,12 @@
1
+# editor backup files
2
+*~
3
+\#*\#
4
+
5
+# compiled code
6
+*.o
7
+*.so
8
+*.dll
9
+*.a
10
+
11
+# SVN stuff
12
+.svn
0 13
new file mode 100644
... ...
@@ -0,0 +1,144 @@
1
+rampInit <- function() {
2
+
3
+    result <- .C("RampRInit",
4
+                 PACKAGE = "mzR")
5
+}
6
+
7
+rampPrintFiles <- function() {
8
+
9
+    result <- .C("RampRPrintFiles",
10
+                 PACKAGE = "mzR")
11
+}
12
+
13
+rampIsFile <- function(filename) {
14
+
15
+    # The C version doesn't do anything extra
16
+    #.C("RampRIsFile",
17
+    #   as.character(filename),
18
+    #   isfile = logical(1),
19
+    #   PACKAGE = "mzR")$isfile
20
+
21
+    if (!file.exists(filename))
22
+        return(FALSE)
23
+    text <- readChar(filename, 1024)
24
+
25
+    length(text) > 0
26
+}
27
+
28
+rampOpen <- function(filename) {
29
+
30
+    result <- .C("RampROpen",
31
+                 as.character(filename),
32
+                 rampid = integer(1),
33
+                 status = integer(1),
34
+                 PACKAGE = "mzR")
35
+
36
+    if (result$status)
37
+        return(result$status)
38
+
39
+    return(result$rampid)
40
+}
41
+
42
+rampClose <- function(rampid) {
43
+
44
+    result <- .C("RampRClose",
45
+                 as.integer(rampid),
46
+                 PACKAGE = "mzR")
47
+}
48
+
49
+rampCloseAll <- function() {
50
+
51
+    result <- .C("RampRCloseAll",
52
+                 PACKAGE = "mzR")
53
+}
54
+
55
+rampNumScans <- function(rampid) {
56
+
57
+    result <- .C("RampRNumScans",
58
+                 as.integer(rampid),
59
+                 numscans = integer(1),
60
+                 status = integer(1),
61
+                 PACKAGE = "mzR")
62
+
63
+    if (result$status)
64
+        return(NA)
65
+
66
+    return(result$numscans)
67
+}
68
+
69
+rampScanHeaders <- function(rampid) {
70
+
71
+    .Call("RampRScanHeaders",
72
+          as.integer(rampid),
73
+          PACKAGE = "mzR")
74
+}
75
+
76
+rampSIPeaks <- function(rampid, seqNum, peaksCount) {
77
+
78
+    if (!is.integer(seqNum))
79
+        seqNum <- as.integer(seqNum)
80
+    if (!is.integer(peaksCount))
81
+        peaksCount <- as.integer(peaksCount)
82
+    .Call("RampRSIPeaks",
83
+          as.integer(rampid),
84
+          seqNum,
85
+          peaksCount,
86
+          PACKAGE = "mzR")
87
+}
88
+
89
+rampRawData <- function(rampid) {
90
+
91
+    scanHeaders <- rampScanHeaders(rampid)
92
+
93
+    # Some of these checks work around buggy RAMP indexing code
94
+    scans <- scanHeaders$msLevel == 1 & scanHeaders$seqNum > 0 &
95
+             !duplicated(scanHeaders$acquisitionNum) &
96
+             scanHeaders$peaksCount > 0
97
+    if ("Full" %in% levels(scanHeaders$scanType))
98
+        scans <- scans & scanHeaders$scanType == "Full"
99
+
100
+    scans <- which(scans)
101
+
102
+    sipeaks <- rampSIPeaks(rampid, scans, scanHeaders$peaksCount[scans])
103
+
104
+    return(list(rt = scanHeaders$retentionTime[scans],
105
+                acquisitionNum = scanHeaders$acquisitionNum[scans],
106
+                tic = scanHeaders$totIonCurrent[scans],
107
+                scanindex = sipeaks$scanindex,
108
+                mz = sipeaks$mz,
109
+                intensity = sipeaks$intensity,
110
+                polarity = scanHeaders$polarity[scans]))
111
+}
112
+
113
+rampRawDataMSn <- function(rampid) {
114
+
115
+    # Check if we have MSn at all
116
+    scanHeaders <- rampScanHeaders(rampid)
117
+    if (max(scanHeaders[,"msLevel"]) < 2) {
118
+        warning("MSn spectra requested but not found")
119
+        return (NULL);
120
+    }
121
+
122
+    # Some of these checks work around buggy RAMP indexing code
123
+    scans <- ( scanHeaders$msLevel >= 2 & scanHeaders$seqNum > 0
124
+              & !duplicated(scanHeaders$acquisitionNum)
125
+              & scanHeaders$peaksCount > 0)
126
+
127
+    scans <- which(scans)
128
+
129
+    sipeaks <- rampSIPeaks(rampid, scans, scanHeaders$peaksCount[scans])
130
+
131
+    retdata <- list(rt = scanHeaders$retentionTime[scans],
132
+                    acquisitionNum = scanHeaders$acquisitionNum[scans],
133
+                    precursorNum=scanHeaders$precursorScanNum[scans],
134
+                    precursorMZ = scanHeaders$precursorMZ[scans],
135
+                    precursorIntensity = scanHeaders$precursorIntensity[scans],
136
+                    peaksCount=scanHeaders$peaksCount[scans],
137
+                    msLevel = scanHeaders$msLevel[scans],
138
+                    precursorCharge = scanHeaders$precursorCharge[scans],
139
+                    scanindex = sipeaks$scanindex, collisionEnergy = scanHeaders$collisionEnergy[scans],
140
+                    mz = sipeaks$mz,
141
+                    intensity =sipeaks$intensity);
142
+
143
+    return(retdata)
144
+}