... | ... |
@@ -17,12 +17,12 @@ Description: mzR provides a unified API to the common file formats and |
17 | 17 |
License: Artistic-2.0 |
18 | 18 |
LazyLoad: yes |
19 | 19 |
Depends: Rcpp (>= 0.10.1), methods, utils |
20 |
-Imports: Biobase, BiocGenerics (>= 0.13.6), ProtGenerics (>= 1.9.1) |
|
20 |
+Imports: Biobase, BiocGenerics (>= 0.13.6), ProtGenerics (>= 1.9.1), ncdf4 |
|
21 | 21 |
Suggests: msdata (>= 0.15.1), RUnit, mzID, BiocStyle (>= 2.5.19), knitr, XML |
22 | 22 |
VignetteBuilder: knitr |
23 | 23 |
LinkingTo: Rcpp, zlibbioc, Rhdf5lib (>= 1.1.4) |
24 | 24 |
RcppModules: Ramp, Pwiz, Ident |
25 |
-SystemRequirements: C++11, GNU make, NetCDF |
|
25 |
+SystemRequirements: C++11, GNU make |
|
26 | 26 |
URL: https://github.com/sneumann/mzR/ |
27 | 27 |
BugReports: https://github.com/sneumann/mzR/issues/ |
28 | 28 |
biocViews: Infrastructure, DataImport, Proteomics, Metabolomics, |
... | ... |
@@ -2,8 +2,10 @@ |
2 | 2 |
## Defines supported backend APIs |
3 | 3 |
## - NULL: default |
4 | 4 |
## - C++Object: for Rcpp modules for ramp and pwiz backends |
5 |
+## - ncdf4 for netCDF files |
|
6 |
+setOldClass("ncdf4") |
|
5 | 7 |
setClassUnion("msAPI", |
6 |
- c("C++Object","integer", "NULL")) |
|
8 |
+ c("C++Object","ncdf4", "NULL")) |
|
7 | 9 |
|
8 | 10 |
############################################################## |
9 | 11 |
## mzR main virtual class |
... | ... |
@@ -60,10 +62,18 @@ setClass("mzRpwiz", |
60 | 62 |
############################################################## |
61 | 63 |
## mzRnetCDF - netCDF backend |
62 | 64 |
setClass("mzRnetCDF", |
63 |
- representation(), |
|
65 |
+ representation(backend="ncdf4"), |
|
64 | 66 |
contains=c("mzR"), |
65 | 67 |
prototype=prototype( |
66 |
- new("Versioned", versions=c(mzR="0.0.1"))) |
|
68 |
+ new("Versioned", versions=c(mzR="0.0.2"))), |
|
69 |
+ validity=function(object) { |
|
70 |
+ msg <- validMsg(NULL,NULL) |
|
71 |
+ if (is.null(object@backend)) |
|
72 |
+ msg <- validMsg(msg,"ncdf4 object not initialised.") |
|
73 |
+ if (is.null(object@backend$id)) |
|
74 |
+ msg <- validMsg(msg,"ncdf4 object is closed.") |
|
75 |
+ if (is.null(msg)) TRUE |
|
76 |
+ else msg } |
|
67 | 77 |
) |
68 | 78 |
|
69 | 79 |
############################################################## |
... | ... |
@@ -1,25 +1,7 @@ |
1 |
-## setMethod("get3Dmap", |
|
2 |
-## signature="mzRnetCDF", |
|
3 |
-## function(object,scans,lowMz,highMz,resMz) |
|
4 |
-## return(object@backend$get3DMap(scans,lowMz,highMz,resMz))) |
|
5 |
- |
|
6 |
-## setMethod("initializeRamp", |
|
7 |
-## signature="mzRnetCDF", |
|
8 |
-## function(object) { |
|
9 |
-## if (!file.exists(fileName(object))) |
|
10 |
-## stop("File ",fileName(object)," not found.\n") |
|
11 |
-## object@backend$open(fileName(object), declaredOnly = TRUE) |
|
12 |
-## if (isInitialized(object)) invisible(TRUE) |
|
13 |
-## else stop("Could not initialize ramp slot.") |
|
14 |
-## }) |
|
15 |
- |
|
16 | 1 |
setMethod("length", |
17 | 2 |
signature=c("mzRnetCDF"), |
18 | 3 |
function(x) { |
19 |
- scanindex <- netCDFVarInt(x@backend, "scan_index") |
|
20 |
- if (!is.null(attr(scanindex, "errortext"))) |
|
21 |
- stop("Couldn't read scan indicies from ", x@backend) |
|
22 |
- return(length(scanindex)) |
|
4 |
+ return(netCDFVarLen(x@backend, var="scan_number")) |
|
23 | 5 |
}) |
24 | 6 |
|
25 | 7 |
setMethod("peaks", "mzRnetCDF", |
... | ... |
@@ -102,11 +84,15 @@ setMethod("header", |
102 | 84 |
|
103 | 85 |
setMethod("close", |
104 | 86 |
signature="mzRnetCDF", |
105 |
- function(con,...) return( netCDFClose(con@backend) )) |
|
87 |
+ function(con,...) { |
|
88 |
+ if (validObject(con)) |
|
89 |
+ netCDFClose(con@backend) |
|
90 |
+ con@backend$id <- NULL |
|
91 |
+ invisible(TRUE)} ) |
|
106 | 92 |
|
107 | 93 |
setMethod("isInitialized", |
108 | 94 |
signature="mzRnetCDF", |
109 |
- function(object) return(object@backend > 0)) |
|
95 |
+ function(object) return(class(object@backend) == "ncdf4" && validObject(object))) |
|
110 | 96 |
|
111 | 97 |
setMethod("runInfo", |
112 | 98 |
signature="mzRnetCDF", |
... | ... |
@@ -1,152 +1,119 @@ |
1 |
-netCDFStrError <- function(ncerr) { |
|
2 |
- |
|
3 |
- buflen <- 255 |
|
4 |
- |
|
5 |
- .C("NetCDFStrError", |
|
6 |
- as.integer(ncerr), |
|
7 |
- as.integer(buflen), |
|
8 |
- out = paste(rep(" ", buflen), collapse = ""), |
|
9 |
- PACKAGE = "mzR")$out |
|
10 |
-} |
|
11 | 1 |
|
12 | 2 |
netCDFIsFile <- function(filename) { |
13 |
- |
|
14 |
- ncid <- netCDFOpen(filename) |
|
15 |
- if (!is.null(attr(ncid, "errortext"))) |
|
16 |
- return(FALSE) |
|
17 |
- netCDFClose(ncid) |
|
18 |
- |
|
19 |
- return(TRUE) |
|
3 |
+ result <- tryCatch({ |
|
4 |
+ ncid <- nc_open(filename) |
|
5 |
+ result <- !is.null(ncid) |
|
6 |
+ netCDFClose(ncid) |
|
7 |
+ return(result) |
|
8 |
+ }, |
|
9 |
+ error=function(cond) return(FALSE) |
|
10 |
+ ) |
|
20 | 11 |
} |
21 | 12 |
|
22 | 13 |
netCDFOpen <- function(filename) { |
23 |
- |
|
24 |
- result <- .C("NetCDFOpen", |
|
25 |
- as.character(filename), |
|
26 |
- ncid = integer(1), |
|
27 |
- status = integer(1), |
|
28 |
- PACKAGE = "mzR") |
|
29 |
- |
|
30 |
- if (result$status) |
|
31 |
- return(structure(result$status, |
|
32 |
- errortext = netCDFStrError(result$status))) |
|
33 |
- |
|
34 |
- return(result$ncid) |
|
14 |
+ result <- nc_open(filename, write=FALSE) |
|
15 |
+ return(result) |
|
35 | 16 |
} |
36 | 17 |
|
37 | 18 |
netCDFClose <- function(ncid) { |
38 |
- |
|
39 |
- result <- .C("NetCDFClose", |
|
40 |
- as.integer(ncid), |
|
41 |
- status = integer(1), |
|
42 |
- PACKAGE = "mzR") |
|
43 |
- |
|
44 |
- if (result$status) |
|
45 |
- return(structure(result$status, |
|
46 |
- errortext = netCDFStrError(result$status))) |
|
47 |
- |
|
48 |
- result$status |
|
19 |
+ result <- tryCatch({ |
|
20 |
+## closedncid <- nc_close(ncid) |
|
21 |
+ return(TRUE) |
|
22 |
+ }, |
|
23 |
+ error=function(cond) return(FALSE) |
|
24 |
+ ) |
|
49 | 25 |
} |
50 | 26 |
|
51 | 27 |
netCDFVarID <- function(ncid, var) { |
52 |
- |
|
53 |
- result <- .C("NetCDFVarID", |
|
54 |
- as.integer(ncid), |
|
55 |
- as.character(var), |
|
56 |
- id = integer(1), |
|
57 |
- status = integer(1), |
|
58 |
- PACKAGE = "mzR") |
|
59 |
- |
|
60 |
- if (result$status) |
|
61 |
- return(structure(result$status, |
|
62 |
- errortext = netCDFStrError(result$status))) |
|
63 |
- |
|
64 |
- return(result$id) |
|
28 |
+stop() |
|
29 |
+ ## result <- .C("NetCDFVarID", |
|
30 |
+ ## as.integer(ncid), |
|
31 |
+ ## as.character(var), |
|
32 |
+ ## id = integer(1), |
|
33 |
+ ## status = integer(1), |
|
34 |
+ ## PACKAGE = "mzR") |
|
35 |
+ |
|
36 |
+ ## if (result$status) |
|
37 |
+ ## return(structure(result$status, |
|
38 |
+ ## errortext = netCDFStrError(result$status))) |
|
39 |
+ |
|
40 |
+ ## return(result$id) |
|
65 | 41 |
} |
66 | 42 |
|
67 | 43 |
netCDFVarLen <- function(ncid, var) { |
68 | 44 |
|
69 |
- if (is.character(var)) |
|
70 |
- var <- netCDFVarID(ncid, var) |
|
71 |
- |
|
72 |
- result <- .C("NetCDFVarLen", |
|
73 |
- as.integer(ncid), |
|
74 |
- as.integer(var), |
|
75 |
- len = integer(1), |
|
76 |
- status = integer(1), |
|
77 |
- PACKAGE = "mzR") |
|
45 |
+ return(ncid$dim[[var]]$len) |
|
78 | 46 |
|
79 |
- if (result$status) |
|
80 |
- return(structure(result$status, |
|
81 |
- errortext = netCDFStrError(result$status))) |
|
82 |
- |
|
83 |
- return(result$len) |
|
84 | 47 |
} |
85 | 48 |
|
86 | 49 |
netCDFVarDouble <- function(ncid, var) { |
50 |
+ as.vector(ncvar_get(ncid, varid=var)) |
|
51 |
+} |
|
52 |
+netCDFVarInt <- function(ncid, var) { |
|
53 |
+ as.vector(ncvar_get(ncid, varid=var)) |
|
54 |
+} |
|
55 |
+netCDFVarText <- function(ncid, var) { |
|
56 |
+ as.vector(ncvar_get(ncid, varid=var)) |
|
57 |
+} |
|
58 |
+ |
|
59 |
+## netCDFVarDouble <- function(ncid, var) { |
|
87 | 60 |
|
88 |
- if (is.character(var)) |
|
89 |
- var <- netCDFVarID(ncid, var) |
|
61 |
+## if (is.character(var)) |
|
62 |
+## var <- netCDFVarID(ncid, var) |
|
90 | 63 |
|
91 |
- if (!is.null(attr(var, "errortext"))) |
|
92 |
- return(var) |
|
64 |
+## if (!is.null(attr(var, "errortext"))) |
|
65 |
+## return(var) |
|
93 | 66 |
|
94 |
- len <- netCDFVarLen(ncid, var) |
|
95 |
- if (!is.null(attr(len, "errortext"))) |
|
96 |
- return(len) |
|
67 |
+## len <- netCDFVarLen(ncid, var) |
|
68 |
+## if (!is.null(attr(len, "errortext"))) |
|
69 |
+## return(len) |
|
97 | 70 |
|
98 |
- .C("NetCDFVarDouble", |
|
99 |
- as.integer(ncid), |
|
100 |
- as.integer(var), |
|
101 |
- data = double(len), |
|
102 |
- status = integer(1), |
|
103 |
- PACKAGE = "mzR")$data |
|
104 |
-} |
|
71 |
+## .C("NetCDFVarDouble", |
|
72 |
+## as.integer(ncid), |
|
73 |
+## as.integer(var), |
|
74 |
+## data = double(len), |
|
75 |
+## status = integer(1), |
|
76 |
+## PACKAGE = "mzR")$data |
|
77 |
+## } |
|
105 | 78 |
|
106 |
-netCDFVarInt <- function(ncid, var) { |
|
79 |
+## netCDFVarInt <- function(ncid, var) { |
|
107 | 80 |
|
108 |
- if (is.character(var)) |
|
109 |
- var <- netCDFVarID(ncid, var) |
|
81 |
+## if (is.character(var)) |
|
82 |
+## var <- netCDFVarID(ncid, var) |
|
110 | 83 |
|
111 |
- if (!is.null(attr(var, "errortext"))) |
|
112 |
- return(var) |
|
84 |
+## if (!is.null(attr(var, "errortext"))) |
|
85 |
+## return(var) |
|
113 | 86 |
|
114 |
- len <- netCDFVarLen(ncid, var) |
|
115 |
- if (!is.null(attr(len, "errortext"))) |
|
116 |
- return(len) |
|
87 |
+## len <- netCDFVarLen(ncid, var) |
|
88 |
+## if (!is.null(attr(len, "errortext"))) |
|
89 |
+## return(len) |
|
117 | 90 |
|
118 |
- .C("NetCDFVarInt", |
|
119 |
- as.integer(ncid), |
|
120 |
- as.integer(var), |
|
121 |
- data = integer(len), |
|
122 |
- status = integer(1), |
|
123 |
- PACKAGE = "mzR")$data |
|
124 |
-} |
|
91 |
+## .C("NetCDFVarInt", |
|
92 |
+## as.integer(ncid), |
|
93 |
+## as.integer(var), |
|
94 |
+## data = integer(len), |
|
95 |
+## status = integer(1), |
|
96 |
+## PACKAGE = "mzR")$data |
|
97 |
+## } |
|
125 | 98 |
|
126 |
-netCDFVarText <- function(ncid, var) { |
|
99 |
+## netCDFVarText <- function(ncid, var) { |
|
127 | 100 |
|
128 |
- if (is.character(var)) |
|
129 |
- var <- netCDFVarID(ncid, var) |
|
101 |
+## if (is.character(var)) |
|
102 |
+## var <- netCDFVarID(ncid, var) |
|
130 | 103 |
|
131 |
- if (!is.null(attr(var, "errortext"))) |
|
132 |
- return(var) |
|
104 |
+## if (!is.null(attr(var, "errortext"))) |
|
105 |
+## return(var) |
|
133 | 106 |
|
134 |
- .C("NetCDFVarText", |
|
135 |
- as.integer(ncid), |
|
136 |
- as.integer(var), |
|
137 |
- data = character(1), |
|
138 |
- status = integer(1), |
|
139 |
- PACKAGE = "mzR")$data |
|
140 |
-} |
|
107 |
+## .C("NetCDFVarText", |
|
108 |
+## as.integer(ncid), |
|
109 |
+## as.integer(var), |
|
110 |
+## data = character(1), |
|
111 |
+## status = integer(1), |
|
112 |
+## PACKAGE = "mzR")$data |
|
113 |
+## } |
|
141 | 114 |
|
142 | 115 |
netCDFAttText <- function(ncid, att) { |
143 |
- |
|
144 |
- .C("NetCDFGlobalAttribute", |
|
145 |
- as.integer(ncid), |
|
146 |
- as.character(att), |
|
147 |
- data = character(1), |
|
148 |
- status = integer(1), |
|
149 |
- PACKAGE = "mzR")$data |
|
116 |
+ ncatt_get(ncid, varid=0, attname=att)$value |
|
150 | 117 |
} |
151 | 118 |
|
152 | 119 |
|
... | ... |
@@ -154,42 +121,34 @@ netCDFMSPoints <- function(ncid, scanIndex) { |
154 | 121 |
|
155 | 122 |
if (!is.integer(scanIndex)) scanIndex <- as.integer(scanIndex) |
156 | 123 |
|
157 |
- var <- netCDFVarID(ncid, "mass_values") |
|
158 |
- if (!is.null(attr(var, "errortext"))) |
|
159 |
- return(var) |
|
160 |
- |
|
161 |
- len <- netCDFVarLen(ncid, var) |
|
162 |
- if (!is.null(attr(len, "errortext"))) |
|
163 |
- return(len) |
|
164 |
- |
|
165 |
- .C("NetCDFMSPoints", |
|
166 |
- as.integer(ncid), |
|
167 |
- as.integer(length(scanIndex)), |
|
168 |
- scanIndex, |
|
169 |
- as.integer(len), |
|
170 |
- massValues = double(len), |
|
171 |
- intensityValues = double(len), |
|
172 |
- status = integer(1), |
|
173 |
- PACKAGE = "mzR")[c("massValues", "intensityValues")] |
|
124 |
+ return (cbind.data.frame(massValues=netCDFVarDouble(ncid, "mass_values"), |
|
125 |
+ intensityValues=netCDFVarDouble(ncid, "intensity_values"))) |
|
126 |
+ |
|
127 |
+ ## var <- netCDFVarID(ncid, "mass_values") |
|
128 |
+ ## if (!is.null(attr(var, "errortext"))) |
|
129 |
+ ## return(var) |
|
130 |
+ |
|
131 |
+ ## len <- netCDFVarLen(ncid, var) |
|
132 |
+ ## if (!is.null(attr(len, "errortext"))) |
|
133 |
+ ## return(len) |
|
134 |
+ |
|
135 |
+ ## .C("NetCDFMSPoints", |
|
136 |
+ ## as.integer(ncid), |
|
137 |
+ ## as.integer(length(scanIndex)), |
|
138 |
+ ## scanIndex, |
|
139 |
+ ## as.integer(len), |
|
140 |
+ ## massValues = double(len), |
|
141 |
+ ## intensityValues = double(len), |
|
142 |
+ ## status = integer(1), |
|
143 |
+ ## PACKAGE = "mzR")[c("massValues", "intensityValues")] |
|
174 | 144 |
} |
175 | 145 |
|
176 | 146 |
netCDFRawData <- function(ncid) { |
177 | 147 |
|
178 | 148 |
rt <- netCDFVarDouble(ncid, "scan_acquisition_time") |
179 |
- if (!is.null(attr(rt, "errortext"))) |
|
180 |
- stop("Couldn't read scan times") |
|
181 |
- |
|
182 | 149 |
tic <- netCDFVarDouble(ncid, "total_intensity") |
183 |
- if (!is.null(attr(tic, "errortext"))) |
|
184 |
- stop("Couldn't read total ion current") |
|
185 |
- |
|
186 |
- scanindex <- netCDFVarInt(ncid, "scan_index") |
|
187 |
- if (!is.null(attr(scanindex, "errortext"))) |
|
188 |
- stop("Couldn't read scan indecies") |
|
189 |
- |
|
150 |
+ scanindex <- netCDFVarInt(ncid, "scan_index") |
|
190 | 151 |
pointValues <- netCDFMSPoints(ncid, scanindex) |
191 |
- if (!is.null(attr(pointValues, "errortext"))) |
|
192 |
- stop("Couldn't read mass/intensity values") |
|
193 | 152 |
|
194 | 153 |
startTimeStamp <- netCDFAttText(ncid, "netcdf_file_date_time_stamp") |
195 | 154 |
return(list(rt = rt, tic = tic, scanindex = scanindex, |
... | ... |
@@ -215,21 +174,9 @@ netCDFRunInfo <- function(ncid) { |
215 | 174 |
netCDFInstrumentInfo <- function(ncid) { |
216 | 175 |
|
217 | 176 |
imodel <- netCDFVarText(ncid, "instrument_name") |
218 |
- if (!is.null(attr(imodel, "errortext"))) |
|
219 |
- stop("Couldn't read instrument_name") |
|
220 |
- |
|
221 | 177 |
imanufacturer <- netCDFVarText(ncid, "instrument_mfr") |
222 |
- if (!is.null(attr(imodel, "errortext"))) |
|
223 |
- stop("Couldn't read instrument_mfr") |
|
224 |
- |
|
225 | 178 |
iionisation <- netCDFAttText(ncid, "test_ionization_mode") |
226 |
- if (!is.null(attr(iionisation, "errortext"))) |
|
227 |
- stop("Couldn't read test_ionization_mode") |
|
228 |
- |
|
229 | 179 |
idetector <- netCDFAttText(ncid, "test_detector_type") |
230 |
- if (!is.null(attr(idetector, "errortext"))) |
|
231 |
- stop("Couldn't read test_detector_type") |
|
232 |
- |
|
233 | 180 |
ianalyzer <- NA |
234 | 181 |
|
235 | 182 |
return(list(model = imodel, manufacturer=imanufacturer, |
... | ... |
@@ -121,12 +121,9 @@ ARCH_OBJS=./boost/libs/thread/src/pthread/once.o \ |
121 | 121 |
RHDF5_LIBS=`echo 'Rhdf5lib::pkgconfig("PKG_CXX_LIBS")'| "${R_HOME}/bin/R" --vanilla --slave` |
122 | 122 |
endif |
123 | 123 |
|
124 |
-NC_CFLAGS=`nc-config --cflags || /bin/true` |
|
125 |
-NC_LIBS=-L/opt/lib/hdf5-18/lib/ `nc-config --libs || echo " -lnetcdf "` |
|
124 |
+MZROBJECTS=cramp.o ramp_base64.o ramp.o RcppRamp.o RcppRampModule.o RcppPwiz.o RcppPwizModule.o RcppIdent.o RcppIdentModule.o |
|
126 | 125 |
|
127 |
-MZROBJECTS=cramp.o ramp_base64.o ramp.o RcppRamp.o RcppRampModule.o rnetCDF.o RcppPwiz.o RcppPwizModule.o RcppIdent.o RcppIdentModule.o |
|
128 |
- |
|
129 |
-OBJECTS= $(MZROBJECTS) $(PWIZOBJECTS) $(ARCH_OBJS) rampR.o R_init_mzR.o |
|
126 |
+OBJECTS= $(MZROBJECTS) $(PWIZOBJECTS) $(ARCH_OBJS) rampR.o |
|
130 | 127 |
|
131 | 128 |
## Generate dependency files |
132 | 129 |
#DEPFLAGS = -MT $@ -MMD -MP |
133 | 130 |
deleted file mode 100644 |
... | ... |
@@ -1,19 +0,0 @@ |
1 |
-#include <R_ext/Rdynload.h> |
|
2 |
-#include "rnetCDF.h" |
|
3 |
- |
|
4 |
-static const R_CMethodDef cMethods[] = { |
|
5 |
- {"NetCDFStrError", (DL_FUNC) &NetCDFStrError, 3}, |
|
6 |
- {"NetCDFOpen", (DL_FUNC) &NetCDFOpen, 3}, |
|
7 |
- {"NetCDFClose", (DL_FUNC) &NetCDFClose, 2}, |
|
8 |
- {"NetCDFVarID", (DL_FUNC) &NetCDFVarID, 4}, |
|
9 |
- {"NetCDFVarLen", (DL_FUNC) &NetCDFVarLen, 4}, |
|
10 |
- {"NetCDFVarDouble", (DL_FUNC) &NetCDFVarDouble, 4}, |
|
11 |
- {"NetCDFVarInt", (DL_FUNC) &NetCDFVarInt, 4}, |
|
12 |
- {"NetCDFMSPoints", (DL_FUNC) &NetCDFMSPoints, 7}, |
|
13 |
- {NULL, NULL, 0} |
|
14 |
-}; |
|
15 |
- |
|
16 |
-void R_init_mzR(DllInfo * info) |
|
17 |
-{ |
|
18 |
- R_registerRoutines(info, cMethods, NULL, NULL, NULL); |
|
19 |
-} |
20 | 0 |
deleted file mode 100755 |
... | ... |
@@ -1,140 +0,0 @@ |
1 |
-#include <string.h> |
|
2 |
-#include "rnetCDF.h" |
|
3 |
- |
|
4 |
-void NetCDFStrError(const int *ncerr, const int *len, char *errortext[]) { |
|
5 |
- |
|
6 |
- strncpy(errortext[0], nc_strerror(*ncerr), *len); |
|
7 |
-} |
|
8 |
- |
|
9 |
-void NetCDFOpen(const char *fileName[], int *ncid, int *status) { |
|
10 |
- |
|
11 |
- *status = nc_open(fileName[0], NC_NOWRITE, ncid); |
|
12 |
-} |
|
13 |
- |
|
14 |
-void NetCDFClose(const int *ncid, int *status) { |
|
15 |
- |
|
16 |
- *status = nc_close(*ncid); |
|
17 |
-} |
|
18 |
- |
|
19 |
-void NetCDFVarID(const int *ncid, const char *varName[], int *varid, int *status) { |
|
20 |
- |
|
21 |
- *status = nc_inq_varid(*ncid, varName[0], varid); |
|
22 |
-} |
|
23 |
- |
|
24 |
-void NetCDFVarLen(const int *ncid, const int *varid, int *len, int *status) { |
|
25 |
- |
|
26 |
- int ndims, dimids[NC_MAX_VAR_DIMS], i; |
|
27 |
- size_t dimLen; |
|
28 |
- |
|
29 |
- if ((*status = nc_inq_varndims(*ncid, *varid, &ndims))) |
|
30 |
- return; |
|
31 |
- |
|
32 |
- if ((*status = nc_inq_vardimid(*ncid, *varid, dimids))) |
|
33 |
- return; |
|
34 |
- |
|
35 |
- *len = 1; |
|
36 |
- for (i = 0; i < ndims; i++) { |
|
37 |
- if ((*status = nc_inq_dimlen(*ncid, dimids[i], &dimLen))) |
|
38 |
- return; |
|
39 |
- *len *= dimLen; |
|
40 |
- } |
|
41 |
-} |
|
42 |
- |
|
43 |
-void NetCDFVarDouble(const int *ncid, const int *varid, double *data, int *status) { |
|
44 |
- |
|
45 |
- int varLen, i; |
|
46 |
- double scaleFactor, addOffset; |
|
47 |
- size_t attLen; |
|
48 |
- |
|
49 |
- NetCDFVarLen(ncid, varid, &varLen, status); |
|
50 |
- if (*status) |
|
51 |
- return; |
|
52 |
- |
|
53 |
- if ((*status = nc_get_var_double(*ncid, *varid, data))) |
|
54 |
- return; |
|
55 |
- |
|
56 |
- if (!nc_inq_att(*ncid, *varid, "scale_factor", NULL, &attLen)) |
|
57 |
- if (attLen == 1 && !nc_get_att_double(*ncid, *varid, "scale_factor", &scaleFactor) && scaleFactor != 1) |
|
58 |
- for (i = 0; i < varLen; i++) |
|
59 |
- data[i] *= scaleFactor; |
|
60 |
- |
|
61 |
- if (!nc_inq_att(*ncid, *varid, "add_offset", NULL, &attLen)) |
|
62 |
- if (attLen == 1 && !nc_get_att_double(*ncid, *varid, "add_offset", &addOffset) && addOffset != 0) |
|
63 |
- for (i = 0; i < varLen; i++) |
|
64 |
- data[i] += addOffset; |
|
65 |
-} |
|
66 |
- |
|
67 |
-void NetCDFVarInt(const int *ncid, const int *varid, int *data, int *status) { |
|
68 |
- |
|
69 |
- int varLen; |
|
70 |
- |
|
71 |
- NetCDFVarLen(ncid, varid, &varLen, status); |
|
72 |
- if (*status) |
|
73 |
- return; |
|
74 |
- |
|
75 |
- *status = nc_get_var_int(*ncid, *varid, data); |
|
76 |
-} |
|
77 |
- |
|
78 |
-void NetCDFVarText(const int *ncid, const int *varid, char **data, int *status) { |
|
79 |
- |
|
80 |
- int varLen; |
|
81 |
- |
|
82 |
- NetCDFVarLen(ncid, varid, &varLen, status); |
|
83 |
- if (*status) |
|
84 |
- return; |
|
85 |
- |
|
86 |
- *status = nc_get_var_text(*ncid, *varid, data[0]); |
|
87 |
-} |
|
88 |
- |
|
89 |
-void NetCDFGlobalAttribute(const int *ncid, const char **attname, char **data, int *status) { |
|
90 |
- |
|
91 |
- size_t attLen; |
|
92 |
- |
|
93 |
- *status = nc_inq_attlen (*ncid, NC_GLOBAL, attname[0], &attLen); |
|
94 |
- if (*status) |
|
95 |
- return; |
|
96 |
- |
|
97 |
- *status = nc_get_att_text(*ncid, NC_GLOBAL, attname[0], data[0]); |
|
98 |
-} |
|
99 |
- |
|
100 |
-void NetCDFMSPoints(const int *ncid, const int *scanNumber, |
|
101 |
- const int *scanIndex, const int *pointNumber, |
|
102 |
- double *massValues, double *intensityValues, int *status) { |
|
103 |
- |
|
104 |
- int varid, i, j, scanLen; |
|
105 |
- double tmpMass, tmpIntensity; |
|
106 |
- |
|
107 |
- *status = nc_inq_varid(*ncid, "mass_values", &varid); |
|
108 |
- if (*status) |
|
109 |
- return; |
|
110 |
- |
|
111 |
- NetCDFVarDouble(ncid, &varid, massValues, status); |
|
112 |
- if (*status) |
|
113 |
- return; |
|
114 |
- |
|
115 |
- *status = nc_inq_varid(*ncid, "intensity_values", &varid); |
|
116 |
- if (*status) |
|
117 |
- return; |
|
118 |
- |
|
119 |
- NetCDFVarDouble(ncid, &varid, intensityValues, status); |
|
120 |
- if (*status) |
|
121 |
- return; |
|
122 |
- |
|
123 |
- for (i = 0; i < *scanNumber-1; i++) |
|
124 |
- if (scanIndex[i+1] - scanIndex[i] > 1) |
|
125 |
- if (massValues[scanIndex[i]] < massValues[scanIndex[i]+1]) |
|
126 |
- return; |
|
127 |
- |
|
128 |
- for (i = 0; i < *scanNumber; i++) { |
|
129 |
- scanLen = (i < *scanNumber - 1) ? scanIndex[i+1] - scanIndex[i] : |
|
130 |
- *pointNumber - scanIndex[i]; |
|
131 |
- for (j = 0; j < scanLen/2; j++) { |
|
132 |
- tmpMass = massValues[scanIndex[i]+j]; |
|
133 |
- tmpIntensity = intensityValues[scanIndex[i]+j]; |
|
134 |
- massValues[scanIndex[i]+j] = massValues[scanIndex[i]+scanLen-1-j]; |
|
135 |
- intensityValues[scanIndex[i]+j] = intensityValues[scanIndex[i]+scanLen-1-j]; |
|
136 |
- massValues[scanIndex[i]+scanLen-1-j] = tmpMass; |
|
137 |
- intensityValues[scanIndex[i]+scanLen-1-j] = tmpIntensity; |
|
138 |
- } |
|
139 |
- } |
|
140 |
-} |
141 | 0 |
deleted file mode 100644 |
... | ... |
@@ -1,23 +0,0 @@ |
1 |
-#include <netcdf.h> |
|
2 |
- |
|
3 |
-void NetCDFStrError(const int *ncerr, const int *len, char *errortext[]); |
|
4 |
- |
|
5 |
-void NetCDFOpen(const char *fileName[], int *ncid, int *status); |
|
6 |
- |
|
7 |
-void NetCDFClose(const int *ncid, int *status); |
|
8 |
- |
|
9 |
-void NetCDFVarID(const int *ncid, const char *varName[], int *varid, int *status); |
|
10 |
- |
|
11 |
-void NetCDFVarLen(const int *ncid, const int *varid, int *len, int *status); |
|
12 |
- |
|
13 |
-void NetCDFVarDouble(const int *ncid, const int *varid, double *data, int *status); |
|
14 |
- |
|
15 |
-void NetCDFVarInt(const int *ncid, const int *varid, int *data, int *status); |
|
16 |
- |
|
17 |
-void NetCDFVarText(const int *ncid, const int *varid, char **data, int *status); |
|
18 |
- |
|
19 |
-void NetCDFGlobalAttribute(const int *ncid, const char **attname, char **data, int *status); |
|
20 |
- |
|
21 |
-void NetCDFMSPoints(const int *ncid, const int *scanNumber, |
|
22 |
- const int *scanIndex, const int *pointNumber, |
|
23 |
- double *massValues, double *intensityValues, int *status); |