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

Last change on this file since 417 was 417, checked in by smasson, 15 years ago

add new keywords to file_interp

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