source: trunk/SRC/Interpolation/file_interp.pro @ 327

Last change on this file since 327 was 327, checked in by pinsard, 17 years ago

modification of headers : mainly blanks around = sign for keywords in declaration of function and pro

  • Property svn:keywords set to Id
File size: 18.6 KB
Line 
1;+
2;
3; @hidden
4;
5;-
6FUNCTION call_interp2d, data, inlon, inlat, inmask, outlon, outlat $
7                      , INIRR=inirr, METHOD=method, SMOOTH=smooth $
8                      , WEIG=weig, ADDR=addr, NAN_VALUE=NaN_value, _EXTRA=ex
9;
10  compile_opt idl2, strictarrsubs
11;
12; for byte, short and long, convert to double before extrapolation and interpolation
13  intype = size(data, /type)
14  if intype LE 3 THEN data = double(temporary(data))
15;
16; take care of NaN values
17  mask = inmask *finite(data)
18;
19  IF keyword_set(NaN_value) THEN BEGIN
20    CASE 1 OF
21      nan_value GT 1.e6:mask = temporary(mask) * (data LT (nan_value-10.))
22      nan_value LT -1.e6:mask = temporary(mask) * (data GT (nan_value+10.))
23      abs(nan_value) LT 1.e-6:mask = temporary(mask) * (data GT 1.e-6)
24      ELSE:mask = temporary(mask) * (data NE nan_value)
25    ENDCASE
26  ENDIF
27; extrapolation
28    IF keyword_set(smooth) THEN data = extrapsmooth(temporary(data), mask, /x_periodic, _extra = ex) $
29    ELSE data = extrapolate(temporary(data), mask, /x_periodic, _extra = ex)
30; interpolation
31  IF NOT keyword_set(inirr) THEN BEGIN
32    data = fromreg(method, temporary(data), inlon, inlat, outlon, outlat, WEIG = weig, ADDR = addr, _extra = ex)
33  ENDIF ELSE BEGIN
34    data = fromirr(method, temporary(data), inlon, inlat, -1, outlon, outlat, -1, WEIG = weig, ADDR = addr)
35  ENDELSE
36
37  if intype LE 3 THEN data = round(temporary(data))
38
39  RETURN, data
40END
41;+
42;
43; @file_comments
44; interpolate a NetCDF file from a grid to another (both regular or not)
45;
46; @categories
47; Interpolation, NetCDF
48;
49; @param filein {in}{type=scalar string}
50; input file name (must exist)
51;
52; @param fileout {in}{type=scalar string}
53; output file name (will be overwritten if already exist)
54;
55; @param gridout {in}{type=scalar string}
56; output grid file name (must exist and must contain the
57; longitude and latitude axis as 1D or 2D arrays)
58;
59; @keyword GRIDIN {type=scalar string}{default=set to filein}
60; define the input grid file name. It must exist and must contain the
61; longitude and latitude axis as 1D or 2D arrays. Useful if
62; filein file doesn't contain longitude and latitude axis
63;
64; @keyword MASKIN {type=scalar string}{default=set to gridin}
65; define the input mask file name. It must exist. The mask will be
66; determined through <pro>ncdf_getmask</pro> according to the keywords
67; inmaskname, ininvmask, inuseasmask, inmissing_value, inaddscl_before
68; (see below)
69;
70; @keyword MASKOUT {type=scalar string}{default=set to gridout}
71; define the output mask file name. It must exist. The mask will be
72; determined through <pro>ncdf_getmask</pro> according to the keywords
73; outmaskname, outinvmask, outuseasmask, outmissing_value,
74; outaddscl_before (see bellow)
75;
76; @keyword KEEP {type=string array}{default=all variables}
77; array defining the name of the variables that must be kept in the
78; output file
79;
80; @keyword REMOVE {type=string array}{default=empty}
81; array defining the name of the variables that will be removed in the
82; output file
83;
84; @keyword METHOD {type=scalar string}{default='bilinear'}
85; interpolation method: can be only 'bilinear' (or 'imoms3' if the input grid
86; is a "regular" grid). A "regular/rectangular grid" is defined as a
87; grid for which each longitude lines have the same latitude and each
88; latitude columns have the same longitude.
89;
90; @keyword SMOOTH {type=scalar 0 or 1}{default=0}
91; activate to use <pro>extrapsmooth</pro> instead of
92; <pro>extrapolate</pro> when extrapolating input data over masked
93; points.
94;
95; @keyword SET_XDIMNAME {type=scalar string}{default=not used}
96; used to defined the name of x dimension in filein input file when
97; gridin keyword is used and when the x dimension name is not the same
98; in filein and gridin files. By default, we assume both file have the
99; same x dimension name.
100;
101; @keyword SET_YDIMNAME {type=scalar string}{default=not used}
102; same as set_xdimname but for y dimension
103;
104; @keyword SET_XAXISNAME {type=scalar string}{default=not used}
105; used to defined the name of the variable containing the x axis in
106; filein input file when gridin keyword is used and when its variable
107; containing the x axis name is not the same. By default, we assume
108; both file have the same x axis name. Not that if filein includes x
109; axis there is no point to use gridin
110;
111; @keyword SET_YAXISNAME {type=scalar string}{default=not used}
112; same as set_xaxisname but for y dimension
113;
114; @keyword INMASKNAME {type=scalar string}{default=not used}
115; A string giving the name of the variable in the file maskin that
116; contains the land/sea mask
117;
118; @keyword OUTMASKNAME {type=scalar string}{default=not used}
119; same as inmaskname but for output mask file maskout
120;
121; @keyword ININVMASK {default=0}{type=scalar: 0 or 1}
122; Inverse the land/sea mask of the input mask file maskin (that should
123; have 0/1 values for land/sea)
124;
125; @keyword OUTINVMASK {default=0}{type=scalar: 0 or 1}
126; same as ininvmask but for output mask file maskout
127;
128; @keyword INUSEASMASK {type=scalar string}
129; A string giving the name of the variable in the input mask file maskin
130; that will be used to build the land/sea mask. In this case the
131; mask is based on the first record (if record dimension
132; exists). The mask is build according to :
133;    1 the keyword missing_value if existing
134;    2 the attribute 'missing_value' if existing
135;    3 NaN values if existing
136;
137; @keyword OUTUSEASMASK {type=scalar string}
138; same as inuseasmask but for output mask file maskout
139;
140; @keyword INMISSING_VALUE {type=scalar}
141; To define (or redefine if the attribute is already existing) the
142; missing values used by INUSEASMASK keyword
143;
144; @keyword OUTMISSING_VALUE {type=scalar}
145; same as inmissing_value but for output mask file maskout
146;
147; @keyword INADDSCL_BEFORE {default=0}{type=scalar: 0 or 1}
148; put 1 to apply add_offset and scale factor on data before looking for
149; missing values when using INUSEASMASK keyword
150;
151; @keyword OUTADDSCL_BEFORE {default=0}{type=scalar: 0 or 1}
152; same as inaddscl_before but for output mask file maskout
153;
154; @keyword NAN_VALUE {type=scalar}{default=not used}
155; define the missing value in input data (missing values are treated
156; like masked values and will be filled with extrapolation before
157; interpolation).
158;
159; @keyword ADDR {type=2d array or variable name}
160; 1) at the first call of file_interp:
161;   This keyword can be set to a named variable (undefined or equal to
162;   0) into which the addresses used to perform the interpolation will
163;   be copied when the current routine exits.
164; 2) Next, once this keyword is set to a defined 2d array, it is used
165;   to bypass the computation of the weights and addresses used to
166;   perform the interpolation. In this case, interpolation is much
167;   faster
168;
169; @keyword WEIG {type=2d array or variable name}
170; (see ADDR)
171;
172; @keyword INXAXISNAME {default='x', 'longitude', 'nav_lon', 'lon', 'lon_rho' or 'NbLongitudes'}{type=scalar string}
173; A string giving the name of the variable containing the x axis in
174; the input grid file gridin
175;
176; @keyword INYAXISNAME {default='y', 'latitude', 'nav_lat','lat', 'lat_rho' or 'NbLatitudes'}{type=scalar string}
177; same as inxaxisname but for the y axis in the input grid file gridin
178;
179; @keyword OUTXAXISNAME {default='x', 'longitude', 'nav_lon', 'lon', 'lon_rho' or 'NbLongitudes'}{type=scalar string}
180; same as inxaxisname but for output grid file gridout
181;
182; @keyword OUTYAXISNAME {default='y', 'latitude', 'nav_lat','lat', 'lat_rho' or 'NbLatitudes'}{type=scalar string}
183; same as inyaxisname but for output grid file gridout
184;
185; @keyword  _EXTRA
186; to use <pro>extrapolate</pro>, <pro>extrapsmooth</pro> and <pro>fromreg</pro> keywords
187;
188; @uses
189; <pro>extrapsmooth</pro>, <pro>extrapolate</pro>, <pro>fromreg</pro> and <pro>fromirr</pro>
190;
191; @restrictions
192;
193; - perform only horizontal interpolations on scalar fields
194; - will fill all masked and missing values before interpolation
195; - attributes (like valid_min...) are not updated
196; - see restrictions of <pro>fromreg</pro> and <pro>fromirr</pro>
197;
198; @examples
199;
200; IDL> file_interp, filein, fileout, gridout, inxaxisname = 'lo', inyaxisname = 'la', keep = ['lo', 'la', 'cond_sed']
201;
202; IDL> file_interp, in, out, gdout, inuseasmask = 'sst', inmissing_value = -1.00000e+30, nan_value = -1000.00
203;
204; @history
205;  September 2007: Sebastien Masson (smasson\@locean-ipsl.upmc.fr)
206;
207; @version
208; $Id$
209;
210;-
211PRO file_interp, filein, fileout, gridout, GRIDIN=gridin, MASKIN=maskin, MASKOUT=maskout $
212               , KEEP=keep, REMOVE=remove, METHOD=method, SMOOTH=smooth $
213               , SET_XDIMNAME=set_xdimname, SET_YDIMNAME=set_ydimname $
214               , SET_XAXISNAME=set_xaxisname, SET_YAXISNAME=set_yaxisname $
215               , INMASKNAME=inmaskname, ININVMASK=ininvmask $
216               , INUSEASMASK=inuseasmask $
217               , INMISSING_VALUE=inmissing_value $
218               , INADDSCL_BEFORE=inaddscl_before $
219               , OUTMASKNAME=outmaskname, OUTINVMASK=outinvmask $
220               , OUTUSEASMASK=outuseasmask $
221               , OUTMISSING_VALUE=outmissing_value $
222               , OUTADDSCL_BEFORE=outaddscl_before $
223               , NAN_VALUE=NaN_value, WEIG=weig, ADDR=addr $
224               , INXAXISNAME=inxaxisname, INYAXISNAME=inyaxisname $
225               , OUTXAXISNAME=outxaxisname, OUTYAXISNAME=outyaxisname $
226               , _EXTRA=ex
227;
228  compile_opt idl2, strictarrsubs
229  revision = '$Id$'
230;
231  IF NOT keyword_set(method) THEN method = 'bilinear'
232;
233; input filenames checks...
234;
235  inid = ncdf_open(filein)
236  ininq = ncdf_inquire(inid)
237
238  outid = ncdf_create(fileout, /clobber)
239  ncdf_control, outid, /nofill
240
241  IF NOT keyword_set(gridin) THEN gridin = filein
242
243  IF NOT keyword_set(maskin) THEN maskin = gridin
244  IF NOT keyword_set(maskout) THEN maskout = gridout
245;
246; Copy global attributes
247;
248  FOR i = 0, ininq.ngatts-1 DO BEGIN
249    name = ncdf_attname(inid, i, /global)
250    dummy = ncdf_attcopy(inid, name, outid, /in_global, /out_global)
251  ENDFOR
252  ncdf_attput, outid, 'Created_by', revision, /GLOBAL
253;
254; x/y dim and x/yaxis informations
255;
256  ncdf_getaxis, gridin, indimidx, indimidy, inlon, inlat, xdimname = inxdimname, ydimname = inydimname $
257                , xaxisname = inxaxisname, yaxisname = inyaxisname
258  get_gridparams, inlon, inlat, jpiin, jpjin, 2
259  IF keyword_set(set_xdimname) THEN inxdimname = set_xdimname
260  IF keyword_set(set_ydimname) THEN inydimname = set_ydimname
261  IF keyword_set(set_xaxisname) THEN inxaxisname = set_xaxisname
262  IF keyword_set(set_yaxisname) THEN inyaxisname = set_yaxisname
263;
264  ncdf_getaxis, gridout, outdimidx, outdimidy, outlon, outlat, xaxisname = outxaxisname, yaxisname = outyaxisname
265  get_gridparams, outlon, outlat, jpiout, jpjout, 2
266;
267; masks
268;
269  inmask = ncdf_getmask(maskin, MASKNAME = inmaskname, INVMASK = ininvmask, USEASMASK = inuseasmask $
270                       , MISSING_VALUE = inmissing_value, ADDSCL_BEFORE = inaddscl_before)
271  inmasksz = size(inmask, /dimensions)
272  IF size(inmask, /n_dimensions) EQ 2 THEN inmasksz = [inmasksz, 0]
273  IF n_elements(inmaskname) EQ 0 THEN inmaskname = 'not defined' ; default definition
274  outmask = ncdf_getmask(maskout, MASKNAME = outmaskname, INVMASK = outinvmask, USEASMASK = outuseasmask $
275                        , MISSING_VALUE = outmissing_value, ADDSCL_BEFORE = outaddscl_before)
276;
277; irregular grids?
278;
279  CASE 0 OF
280    array_equal(inlon[*, 0], inlon[*, jpjin-1]):inirr = 1b
281    array_equal(inlat[0, *], inlat[jpiin-1, *]):inirr = 1b
282    array_equal(inlon, inlon[*, 0]#replicate(1, jpjin)):inirr = 1b
283    array_equal(inlat, replicate(1, jpiin)#(inlat[0, *])[*]):inirr = 1b
284    ELSE:inirr = 0b
285  ENDCASE
286  CASE 0 OF
287    array_equal(outlon[*, 0], outlon[*, jpjout-1]):outirr = 1b
288    array_equal(outlat[0, *], outlat[jpiout-1, *]):outirr = 1b
289    array_equal(outlon, outlon[*, 0]#replicate(1, jpjout)):outirr = 1b
290    array_equal(outlat, replicate(1, jpiout)#(outlat[0, *])[*]):outirr = 1b
291    ELSE:outirr = 0b
292  ENDCASE
293
294  IF inirr AND method NE 'bilinear' THEN stop
295;
296; Dimensions
297;
298  indimsz = lonarr(ininq.ndims)
299  outdimsz = lonarr(ininq.ndims)
300  outdimid = lonarr(ininq.ndims)
301  FOR i = 0, ininq.ndims-1 DO BEGIN
302    ncdf_diminq, inid, i, name, size
303    indimsz[i] = size
304    outdimsz[i] = size
305    CASE 1 OF
306      strlowcase(name) EQ strlowcase(inxdimname): BEGIN
307        outdimid[i] = ncdf_dimdef(outid, name, jpiout)
308        outdimsz[i] = jpiout
309        indimx = i
310        outdimx = outdimid[i]
311      END
312      strlowcase(name) EQ strlowcase(inydimname): BEGIN
313        outdimid[i] = ncdf_dimdef(outid, name, jpjout)
314        outdimsz[i] = jpjout
315        indimy = i
316        outdimy = outdimid[i]
317      END
318      i EQ ininq.recdim: outdimid[i] = ncdf_dimdef(outid, name, /UNLIMITED)
319      ELSE: outdimid[i] = ncdf_dimdef(outid, name, size)
320    ENDCASE
321  ENDFOR
322;
323; Variables
324;
325  outvarid = lonarr(ininq.nvars)
326  FOR i = 0, ininq.nvars-1 DO BEGIN
327    varinq = ncdf_varinq(inid, i)
328    okvar = 1
329    IF keyword_set(keep) THEN okvar = total(strlowcase(keep) EQ strlowcase(varinq.name)) EQ 1
330    IF keyword_set(remove) THEN okvar = total(strlowcase(remove) EQ strlowcase(varinq.name)) EQ 0
331    IF okvar THEN BEGIN
332      IF varinq.ndims EQ 0 THEN BEGIN ; scalar variable
333        outvarid[i] = ncdf_vardef(outid, varinq.name $
334                                  , BYTE = varinq.datatype EQ 'BYTE', CHAR = varinq.datatype EQ 'CHAR' $
335                                  , SHORT = varinq.datatype EQ 'INT', LONG = varinq.datatype EQ 'LONG' $
336                                  , FLOAT = varinq.datatype EQ 'FLOAT', DOUBLE = varinq.datatype EQ 'DOUBLE')
337      ENDIF ELSE BEGIN          ; array
338        CASE 1 OF
339          strlowcase(varinq.name) EQ strlowcase(inxaxisname):BEGIN ; xaxis
340            IF outirr THEN dimvar = [outdimx, outdimy] ELSE dimvar = [outdimx]
341          END
342          strlowcase(varinq.name) EQ strlowcase(inyaxisname):BEGIN ; yaxis
343            IF outirr THEN dimvar = [outdimx, outdimy] ELSE dimvar = [outdimy]
344          END
345          strlowcase(varinq.name) EQ strlowcase(inmaskname):BEGIN ; mask
346            IF outmask[0] NE -1 THEN dimvar = outdimid[varinq.dim] ELSE dimvar = -1
347          END
348          (total(varinq.dim EQ indimx) + total(varinq.dim EQ indimx)) EQ 1: dimvar = -1 ; strange variable...
349          ELSE: dimvar = outdimid[varinq.dim]
350        ENDCASE
351        IF dimvar[0] NE -1 THEN BEGIN
352          outvarid[i] = ncdf_vardef(outid, varinq.name, dimvar $
353                                    , BYTE = varinq.datatype EQ 'BYTE', CHAR = varinq.datatype EQ 'CHAR' $
354                                    , SHORT = varinq.datatype EQ 'INT', LONG = varinq.datatype EQ 'LONG' $
355                                    , FLOAT = varinq.datatype EQ 'FLOAT', DOUBLE = varinq.datatype EQ 'DOUBLE')
356        ENDIF ELSE outvarid[i] = - 1
357      ENDELSE
358; Variables attributes
359      IF outvarid[i] NE - 1 THEN BEGIN
360        FOR j = 0, varinq.natts-1 DO BEGIN
361          name = ncdf_attname(inid, i, j)
362          dummy = ncdf_attcopy(inid, i, name, outid, outvarid[i])
363        ENDFOR
364      ENDIF
365    ENDIF ELSE outvarid[i] = -1
366  ENDFOR
367;
368  ncdf_control, outid, /endef
369;
370  FOR i = 0, ininq.nvars-1 DO BEGIN
371    IF outvarid[i] NE -1 THEN BEGIN
372      varinq = ncdf_varinq(inid, i)
373      IF varinq.ndims GE 2 THEN BEGIN
374        interp = varinq.dim[0] EQ indimx AND varinq.dim[1] EQ indimy
375      ENDIF ELSE interp = 0b
376      CASE 1 OF
377        strlowcase(varinq.name) EQ strlowcase(inxaxisname):BEGIN ; x axis
378          IF outirr THEN ncdf_varput, outid, outvarid[i], outlon $
379          ELSE ncdf_varput, outid, outvarid[i], outlon[*, 0]
380        END
381        strlowcase(varinq.name) EQ strlowcase(inyaxisname):BEGIN ; y axis
382          IF outirr THEN ncdf_varput, outid, outvarid[i], outlat $
383          ELSE ncdf_varput, outid, outvarid[i], reform(outlat[0, *])
384        END
385        strlowcase(varinq.name) EQ strlowcase(inmaskname):BEGIN ; mask
386          ncdf_varput, outid, outvarid[i], outmask
387        END
388        ELSE:BEGIN
389          CASE varinq.ndims OF
390            0:BEGIN             ; salar
391              ncdf_varget, inid, i, data
392              ncdf_varput, outid, outvarid[i], temporary(data)
393            END
394            1:BEGIN             ; 1D
395              ncdf_varget, inid, i, data
396              ncdf_varput, outid, outvarid[i], temporary(data)
397            END
398            2:BEGIN             ; 2D
399              ncdf_varget, inid, i, data
400              IF interp THEN data = call_interp2d(temporary(data), inlon, inlat, inmask[*, *, 0], outlon, outlat $
401                                                  , INIRR = inirr, METHOD = method, SMOOTH = smooth $
402                                                  , WEIG = weig, ADDR = addr, NAN_VALUE = NaN_value, _extra = ex)
403              ncdf_varput, outid, outvarid[i], temporary(data)
404            END
405            3:BEGIN             ; 3D
406              FOR k = 0, indimsz[varinq.dim[2]]-1 DO BEGIN
407                incnt = [indimsz[varinq.dim[0: 1]], 1]
408                outcnt = [outdimsz[varinq.dim[0: 1]], 1]
409                off = [0, 0, k]
410                ncdf_varget, inid, i, data, offset = off, count = incnt
411                IF n_elements(inmasksz) GE 3 THEN BEGIN
412                  IF inmasksz[2] EQ indimsz[varinq.dim[2]] AND varinq.dim[2] NE ininq.recdim THEN tmpmsk = inmask[*, *, k] $
413                  ELSE tmpmsk = inmask[*, *, 0]
414                ENDIF ELSE tmpmsk = inmask[*, *, 0]
415                IF interp THEN data = call_interp2d(temporary(data), inlon, inlat, temporary(tmpmsk), outlon, outlat $
416                                                    , INIRR = inirr, METHOD = method, SMOOTH = smooth $
417                                                    , WEIG = weig, ADDR = addr, NAN_VALUE = NaN_value, _extra = ex)
418                ncdf_varput, outid, outvarid[i], temporary(data), offset = off, count = outcnt
419              ENDFOR
420            END
421            4:BEGIN             ; 4D
422              FOR t = 0, indimsz[varinq.dim[3]]-1 DO BEGIN
423                FOR k = 0, indimsz[varinq.dim[2]]-1 DO BEGIN
424                  incnt = [indimsz[varinq.dim[0: 1]], 1, 1]
425                  outcnt = [outdimsz[varinq.dim[0: 1]], 1, 1]
426                  off = [0, 0, k, t]
427                  ncdf_varget, inid, i, data, offset = off, count = incnt
428                  IF n_elements(inmasksz) GE 3 THEN BEGIN
429                    IF inmasksz[2] EQ indimsz[varinq.dim[2]] THEN tmpmsk = inmask[*, *, k] ELSE tmpmsk = inmask
430                  ENDIF ELSE tmpmsk = inmask[*, *, 0]
431                  IF interp THEN data = call_interp2d(temporary(data), inlon, inlat, temporary(tmpmsk), outlon, outlat $
432                                                      , INIRR = inirr, METHOD = method, SMOOTH = smooth $
433                                                      , WEIG = weig, ADDR = addr, NAN_VALUE = NaN_value, _extra = ex)
434                  ncdf_varput, outid, outvarid[i], temporary(data), offset = off, count = outcnt
435                ENDFOR
436              ENDFOR
437            END
438          ENDCASE
439        END
440      ENDCASE
441    ENDIF
442  ENDFOR
443
444  ncdf_close, inid
445  ncdf_close, outid
446
447  return
448END
Note: See TracBrowser for help on using the repository browser.