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

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

bugfix in file_interp with missing values

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