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

Last change on this file since 449 was 449, checked in by smasson, 13 years ago

bugfix related to previous commit

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