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

Last change on this file since 343 was 343, checked in by smasson, 16 years ago

small bugfix + new keyword in file_interp

  • Property svn:keywords set to Id
File size: 20.0 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) * (abs(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
130; that will be used to build the input land/sea mask. In this case the
131; mask is based on the first record (if record dimension
132; exists). The input mask is build according to operator defined by INTESTOP
133; keyword (default NE) and the testing values defined as
134;   1) the second word of TESTOP if existing
135;   2) MISSING_VALUE keyword
136;   3) attribute missing_value or _fillvalue of the variable USEASMASK
137;   4) !Values.f_nan (can be used only with NE and EQ operators)
138;
139; @keyword OUTUSEASMASK {type=scalar string}
140; same as inuseasmask but for output mask file maskout
141;
142; @keyword INMISSING_VALUE {type=scalar}
143; To define (or redefine if the attribute is already existing) the
144; missing values used with INUSEASMASK keyword. Note that this value is
145; not used if INTESTOP keyword is given and contains 2 words. 
146;
147; @keyword OUTMISSING_VALUE {type=scalar}
148; same as inmissing_value but for output mask file maskout
149;
150; @keyword INTESTOP {default='NE'} {type=scalar string, for example 'GT 0.5'}
151; a string describing the type of test that will be done to define the
152; input mask. The test is performed on the variable specified by INUSEASMASK
153; keyword.
154; INTESTOP can contain 1 or 2 words. The first word is the operator
155; definition: "EQ" "NE" "GE" "GT" "LE" "LT" (default is NE). The
156; second word define the testing value. If TESTOP contains only 1
157; word, then the test value is denifed by
158;   1) MISSING_VALUE keyword
159;   2) attribute missing_value or _fillvalue of the variable USEASMASK
160;   3) !Values.f_nan (can be used only with NE and EQ operators)
161;
162; @keyword OUTTESTOP {default='NE'} {type=scalar string, for example 'GT 0.5'}
163; same as INTESTOP but for output mask file maskout
164;
165; @keyword INADDSCL_BEFORE {default=0}{type=scalar: 0 or 1}
166; put 1 to apply add_offset and scale factor on data before looking for
167; missing values when using INUSEASMASK keyword
168;
169; @keyword OUTADDSCL_BEFORE {default=0}{type=scalar: 0 or 1}
170; same as inaddscl_before but for output mask file maskout
171;
172; @keyword NAN_VALUE {type=scalar}{default=not used}
173; define the missing value in input data (missing values are treated
174; like masked values and will be filled with extrapolation before
175; interpolation).
176;
177; @keyword ADDR {type=2d array or variable name}
178; 1) at the first call of file_interp:
179;   This keyword can be set to a named variable (undefined or equal to
180;   0) into which the addresses used to perform the interpolation will
181;   be copied when the current routine exits.
182; 2) Next, once this keyword is set to a defined 2d array, it is used
183;   to bypass the computation of the weights and addresses used to
184;   perform the interpolation. In this case, interpolation is much
185;   faster
186;
187; @keyword WEIG {type=2d array or variable name}
188; (see ADDR)
189;
190; @keyword INXAXISNAME {default='x', 'longitude', 'nav_lon', 'lon', 'lon_rho' or 'NbLongitudes'}{type=scalar string}
191; A string giving the name of the variable containing the x axis in
192; the input grid file gridin
193;
194; @keyword INYAXISNAME {default='y', 'latitude', 'nav_lat','lat', 'lat_rho' or 'NbLatitudes'}{type=scalar string}
195; same as inxaxisname but for the y axis in the input grid file gridin
196;
197; @keyword OUTXAXISNAME {default='x', 'longitude', 'nav_lon', 'lon', 'lon_rho' or 'NbLongitudes'}{type=scalar string}
198; same as inxaxisname but for output grid file gridout
199;
200; @keyword OUTYAXISNAME {default='y', 'latitude', 'nav_lat','lat', 'lat_rho' or 'NbLatitudes'}{type=scalar string}
201; same as inyaxisname but for output grid file gridout
202;
203; @keyword  _EXTRA
204; to use <pro>extrapolate</pro>, <pro>extrapsmooth</pro> and <pro>fromreg</pro> keywords
205;
206; @uses
207; <pro>extrapsmooth</pro>, <pro>extrapolate</pro>, <pro>fromreg</pro> and <pro>fromirr</pro>
208;
209; @restrictions
210;
211; - perform only horizontal interpolations on scalar fields
212; - all masked and missing values are filled before interpolation
213;   -> output data are not masked and have values everywhere.
214; - attributes (like valid_min...) are not updated
215; - see restrictions of <pro>fromreg</pro> and <pro>fromirr</pro>
216; - output mask is not used but, if the input file contains the mask
217;   in a variable (defined by inmaskname), this variable will contain
218;   the output mask in the ouput file
219;
220; @examples
221;
222; IDL> file_interp, filein, fileout, gridout, inxaxisname = 'lo', inyaxisname = 'la', keep = ['lo', 'la', 'cond_sed']
223;
224; IDL> file_interp, in, out, gdout, inuseasmask = 'sst', inmissing_value = -1.00000e+30, nan_value = -1000.00
225;
226; @history
227;  September 2007: Sebastien Masson (smasson\@locean-ipsl.upmc.fr)
228;
229; @version
230; $Id$
231;
232;-
233PRO file_interp, filein, fileout, gridout, GRIDIN=gridin, MASKIN=maskin, MASKOUT=maskout $
234               , KEEP=keep, REMOVE=remove, METHOD=method, SMOOTH=smooth $
235               , SET_XDIMNAME=set_xdimname, SET_YDIMNAME=set_ydimname $
236               , SET_XAXISNAME=set_xaxisname, SET_YAXISNAME=set_yaxisname $
237               , INMASKNAME=inmaskname, ININVMASK=ininvmask $
238               , INUSEASMASK=inuseasmask, INMISSING_VALUE=inmissing_value $
239               , INADDSCL_BEFORE=inaddscl_before, INTESTOP = intestop $
240               , OUTMASKNAME=outmaskname, OUTINVMASK=outinvmask $
241               , OUTUSEASMASK=outuseasmask, OUTMISSING_VALUE=outmissing_value $
242               , OUTADDSCL_BEFORE=outaddscl_before, OUTTESTOP = outtestop $
243               , NAN_VALUE=NaN_value, WEIG=weig, ADDR=addr $
244               , INXAXISNAME=inxaxisname, INYAXISNAME=inyaxisname $
245               , OUTXAXISNAME=outxaxisname, OUTYAXISNAME=outyaxisname $
246               , _EXTRA=ex
247;
248  compile_opt idl2, strictarrsubs
249  revision = '$Id$'
250;
251  IF NOT keyword_set(method) THEN method = 'bilinear'
252;
253; input filenames checks...
254;
255  inid = ncdf_open(filein)
256  ininq = ncdf_inquire(inid)
257
258  outid = ncdf_create(fileout, /clobber)
259  ncdf_control, outid, /nofill
260
261  IF NOT keyword_set(gridin) THEN gridin = filein
262
263  IF NOT keyword_set(maskin) THEN maskin = gridin
264  IF NOT keyword_set(maskout) THEN maskout = gridout
265;
266; Copy global attributes
267;
268  FOR i = 0, ininq.ngatts-1 DO BEGIN
269    name = ncdf_attname(inid, i, /global)
270    dummy = ncdf_attcopy(inid, name, outid, /in_global, /out_global)
271  ENDFOR
272  ncdf_attput, outid, 'Created_by', revision, /GLOBAL
273;
274; x/y dim and x/yaxis informations
275;
276  ncdf_getaxis, gridin, indimidx, indimidy, inlon, inlat, xdimname = inxdimname, ydimname = inydimname $
277                , xaxisname = inxaxisname, yaxisname = inyaxisname
278  get_gridparams, inlon, inlat, jpiin, jpjin, 2
279  IF keyword_set(set_xdimname) THEN inxdimname = set_xdimname
280  IF keyword_set(set_ydimname) THEN inydimname = set_ydimname
281  IF keyword_set(set_xaxisname) THEN inxaxisname = set_xaxisname
282  IF keyword_set(set_yaxisname) THEN inyaxisname = set_yaxisname
283;
284  ncdf_getaxis, gridout, outdimidx, outdimidy, outlon, outlat, xaxisname = outxaxisname, yaxisname = outyaxisname
285  get_gridparams, outlon, outlat, jpiout, jpjout, 2
286;
287; masks
288;
289  inmask = ncdf_getmask(maskin, MASKNAME = inmaskname, INVMASK = ininvmask, USEASMASK = inuseasmask $
290                       , MISSING_VALUE = inmissing_value, ADDSCL_BEFORE = inaddscl_before, TESTOP = intestop)
291  inmasksz = size(inmask, /dimensions)
292  IF size(inmask, /n_dimensions) EQ 2 THEN inmasksz = [inmasksz, 0]
293  IF n_elements(inmaskname) EQ 0 THEN inmaskname = 'not defined' ; default definition
294  outmask = ncdf_getmask(maskout, MASKNAME = outmaskname, INVMASK = outinvmask, USEASMASK = outuseasmask $
295                        , MISSING_VALUE = outmissing_value, ADDSCL_BEFORE = outaddscl_before, TESTOP = outtestop)
296;
297; irregular grids?
298;
299  CASE 0 OF
300    array_equal(inlon[*, 0], inlon[*, jpjin-1]):inirr = 1b
301    array_equal(inlat[0, *], inlat[jpiin-1, *]):inirr = 1b
302    array_equal(inlon, inlon[*, 0]#replicate(1, jpjin)):inirr = 1b
303    array_equal(inlat, replicate(1, jpiin)#(inlat[0, *])[*]):inirr = 1b
304    ELSE:inirr = 0b
305  ENDCASE
306  CASE 0 OF
307    array_equal(outlon[*, 0], outlon[*, jpjout-1]):outirr = 1b
308    array_equal(outlat[0, *], outlat[jpiout-1, *]):outirr = 1b
309    array_equal(outlon, outlon[*, 0]#replicate(1, jpjout)):outirr = 1b
310    array_equal(outlat, replicate(1, jpiout)#(outlat[0, *])[*]):outirr = 1b
311    ELSE:outirr = 0b
312  ENDCASE
313
314  IF inirr AND method NE 'bilinear' THEN stop
315;
316; Dimensions
317;
318  indimsz = lonarr(ininq.ndims)
319  outdimsz = lonarr(ininq.ndims)
320  outdimid = lonarr(ininq.ndims)
321  FOR i = 0, ininq.ndims-1 DO BEGIN
322    ncdf_diminq, inid, i, name, size
323    indimsz[i] = size
324    outdimsz[i] = size
325    CASE 1 OF
326      strlowcase(name) EQ strlowcase(inxdimname): BEGIN
327        outdimid[i] = ncdf_dimdef(outid, name, jpiout)
328        outdimsz[i] = jpiout
329        indimx = i
330        outdimx = outdimid[i]
331      END
332      strlowcase(name) EQ strlowcase(inydimname): BEGIN
333        outdimid[i] = ncdf_dimdef(outid, name, jpjout)
334        outdimsz[i] = jpjout
335        indimy = i
336        outdimy = outdimid[i]
337      END
338      i EQ ininq.recdim: outdimid[i] = ncdf_dimdef(outid, name, /UNLIMITED)
339      ELSE: outdimid[i] = ncdf_dimdef(outid, name, size)
340    ENDCASE
341  ENDFOR
342;
343; Variables
344;
345  outvarid = lonarr(ininq.nvars)
346  FOR i = 0, ininq.nvars-1 DO BEGIN
347    varinq = ncdf_varinq(inid, i)
348    okvar = 1
349    IF keyword_set(keep) THEN okvar = total(strlowcase(keep) EQ strlowcase(varinq.name)) EQ 1
350    IF keyword_set(remove) THEN okvar = total(strlowcase(remove) EQ strlowcase(varinq.name)) EQ 0
351    IF okvar THEN BEGIN
352      IF varinq.ndims EQ 0 THEN BEGIN ; scalar variable
353        outvarid[i] = ncdf_vardef(outid, varinq.name $
354                                  , BYTE = varinq.datatype EQ 'BYTE', CHAR = varinq.datatype EQ 'CHAR' $
355                                  , SHORT = varinq.datatype EQ 'INT' OR varinq.datatype EQ 'SHORT' $
356                                  , LONG = varinq.datatype EQ 'LONG' $
357                                  , FLOAT = varinq.datatype EQ 'FLOAT', DOUBLE = varinq.datatype EQ 'DOUBLE')
358      ENDIF ELSE BEGIN          ; array
359        CASE 1 OF
360          strlowcase(varinq.name) EQ strlowcase(inxaxisname):BEGIN ; xaxis
361            IF outirr THEN dimvar = [outdimx, outdimy] ELSE dimvar = [outdimx]
362          END
363          strlowcase(varinq.name) EQ strlowcase(inyaxisname):BEGIN ; yaxis
364            IF outirr THEN dimvar = [outdimx, outdimy] ELSE dimvar = [outdimy]
365          END
366          strlowcase(varinq.name) EQ strlowcase(inmaskname):BEGIN ; mask
367            IF outmask[0] NE -1 THEN dimvar = outdimid[varinq.dim] ELSE dimvar = -1
368          END
369          (total(varinq.dim EQ indimx) + total(varinq.dim EQ indimx)) EQ 1: dimvar = -1 ; strange variable...
370          ELSE: dimvar = outdimid[varinq.dim]
371        ENDCASE
372        IF dimvar[0] NE -1 THEN BEGIN
373          outvarid[i] = ncdf_vardef(outid, varinq.name, dimvar $
374                                    , BYTE = varinq.datatype EQ 'BYTE', CHAR = varinq.datatype EQ 'CHAR' $
375                                    , SHORT = varinq.datatype EQ 'INT' OR varinq.datatype EQ 'SHORT' $
376                                    , LONG = varinq.datatype EQ 'LONG' $
377                                    , FLOAT = varinq.datatype EQ 'FLOAT', DOUBLE = varinq.datatype EQ 'DOUBLE')
378        ENDIF ELSE outvarid[i] = - 1
379      ENDELSE
380; Variables attributes
381      IF outvarid[i] NE - 1 THEN BEGIN
382        FOR j = 0, varinq.natts-1 DO BEGIN
383          name = ncdf_attname(inid, i, j)
384          dummy = ncdf_attcopy(inid, i, name, outid, outvarid[i])
385        ENDFOR
386      ENDIF
387    ENDIF ELSE outvarid[i] = -1
388  ENDFOR
389;
390  ncdf_control, outid, /endef
391;
392  FOR i = 0, ininq.nvars-1 DO BEGIN
393    IF outvarid[i] NE -1 THEN BEGIN
394      varinq = ncdf_varinq(inid, i)
395      IF varinq.ndims GE 2 THEN BEGIN
396        interp = varinq.dim[0] EQ indimx AND varinq.dim[1] EQ indimy
397      ENDIF ELSE interp = 0b
398      CASE 1 OF
399        strlowcase(varinq.name) EQ strlowcase(inxaxisname):BEGIN ; x axis
400          IF outirr THEN ncdf_varput, outid, outvarid[i], outlon $
401          ELSE ncdf_varput, outid, outvarid[i], outlon[*, 0]
402        END
403        strlowcase(varinq.name) EQ strlowcase(inyaxisname):BEGIN ; y axis
404          IF outirr THEN ncdf_varput, outid, outvarid[i], outlat $
405          ELSE ncdf_varput, outid, outvarid[i], reform(outlat[0, *])
406        END
407        strlowcase(varinq.name) EQ strlowcase(inmaskname):BEGIN ; mask
408          ncdf_varput, outid, outvarid[i], outmask
409        END
410        ELSE:BEGIN
411          CASE varinq.ndims OF
412            0:BEGIN             ; salar
413              ncdf_varget, inid, i, data
414              ncdf_varput, outid, outvarid[i], temporary(data)
415            END
416            1:BEGIN             ; 1D
417              ncdf_varget, inid, i, data
418              ncdf_varput, outid, outvarid[i], temporary(data)
419            END
420            2:BEGIN             ; 2D
421              ncdf_varget, inid, i, data
422              IF interp THEN data = call_interp2d(temporary(data), inlon, inlat, inmask[*, *, 0], outlon, outlat $
423                                                  , INIRR = inirr, METHOD = method, SMOOTH = smooth $
424                                                  , WEIG = weig, ADDR = addr, NAN_VALUE = NaN_value, _extra = ex)
425              ncdf_varput, outid, outvarid[i], temporary(data)
426            END
427            3:BEGIN             ; 3D
428              FOR k = 0, indimsz[varinq.dim[2]]-1 DO BEGIN
429                incnt = [indimsz[varinq.dim[0: 1]], 1]
430                outcnt = [outdimsz[varinq.dim[0: 1]], 1]
431                off = [0, 0, k]
432                ncdf_varget, inid, i, data, offset = off, count = incnt
433                IF n_elements(inmasksz) GE 3 THEN BEGIN
434                  IF inmasksz[2] EQ indimsz[varinq.dim[2]] AND varinq.dim[2] NE ininq.recdim THEN tmpmsk = inmask[*, *, k] $
435                  ELSE tmpmsk = inmask[*, *, 0]
436                ENDIF ELSE tmpmsk = inmask[*, *, 0]
437                IF interp THEN data = call_interp2d(temporary(data), inlon, inlat, temporary(tmpmsk), outlon, outlat $
438                                                    , INIRR = inirr, METHOD = method, SMOOTH = smooth $
439                                                    , WEIG = weig, ADDR = addr, NAN_VALUE = NaN_value, _extra = ex)
440                ncdf_varput, outid, outvarid[i], temporary(data), offset = off, count = outcnt
441              ENDFOR
442            END
443            4:BEGIN             ; 4D
444              FOR t = 0, indimsz[varinq.dim[3]]-1 DO BEGIN
445                FOR k = 0, indimsz[varinq.dim[2]]-1 DO BEGIN
446                  incnt = [indimsz[varinq.dim[0: 1]], 1, 1]
447                  outcnt = [outdimsz[varinq.dim[0: 1]], 1, 1]
448                  off = [0, 0, k, t]
449                  ncdf_varget, inid, i, data, offset = off, count = incnt
450                  IF n_elements(inmasksz) GE 3 THEN BEGIN
451                    IF inmasksz[2] EQ indimsz[varinq.dim[2]] THEN tmpmsk = inmask[*, *, k] ELSE tmpmsk = inmask
452                  ENDIF ELSE tmpmsk = inmask[*, *, 0]
453                  IF interp THEN data = call_interp2d(temporary(data), inlon, inlat, temporary(tmpmsk), outlon, outlat $
454                                                      , INIRR = inirr, METHOD = method, SMOOTH = smooth $
455                                                      , WEIG = weig, ADDR = addr, NAN_VALUE = NaN_value, _extra = ex)
456                  ncdf_varput, outid, outvarid[i], temporary(data), offset = off, count = outcnt
457                ENDFOR
458              ENDFOR
459            END
460          ENDCASE
461        END
462      ENDCASE
463    ENDIF
464  ENDFOR
465
466  ncdf_close, inid
467  ncdf_close, outid
468
469  return
470END
Note: See TracBrowser for help on using the repository browser.