source: trunk/SRC/Grid/ncdf_meshread.pro @ 155

Last change on this file since 155 was 155, checked in by smasson, 18 years ago

some light header cleaning...

  • Property svn:keywords set to Id
File size: 23.4 KB
Line 
1;------------------------------------------------------------
2;------------------------------------------------------------
3;------------------------------------------------------------
4;+
5;
6; @file_comments read NetCDF meshmask file created by OPA
7;
8; @categories grid reading
9;
10; @examples
11; IDL> ncdf_meshread [,' filename']
12;
13; @param filename {in}{optional}{default=meshmask.nc}
14;    the name of the meshmask file to read.
15;    if this name does not contain any "/" and if
16;    iodirectory keyword is not specify, then the common variable
17;    iodir will be use to define the mesh file path.
18;
19; @keyword GLAMBOUNDARY a 2 elements vector, [lon1,lon2], the longitude
20;    boundaries that should be used to visualize the data.
21;      lon2 > lon1
22;      lon2 - lon1 le 360
23;    key_shift will be automaticaly defined according to GLAMBOUNDARY.
24;
25; @keyword CHECKDAT Suppressed. Use micromeshmask.pro to create an
26;    appropriate meshmask.
27;
28; @keyword ONEARTH = 0 or 1 to force the manual definition of
29;    key_onearth (to specify if the data are on earth -> use longitude
30;    /latitude etc...). By default, key_onearth = 1.
31;    note that ONEARTH = 0 forces PERIODIC = 0, SHIFT = 0 and is
32;    cancelling GLAMBOUNDARY
33;
34; @keyword GETDIMENSIONS
35;    Activate this keywords if you only want to know the dimension
36;    of the domain stored in the mesh file. This dimensions will be
37;    defined in jpiglo, jpjglo, jpkglo (cm_4mesh common variables)
38;
39; @keyword PERIODIC = 0 or 1 to force the manual definition of
40;    key_periodic. By default, key_periodic is automaticaly
41;    computed by using the first line of glamt.
42;
43; @keyword SHIFT to force the manual definition of key_shift. By
44;    default, key_shift is automaticaly computed according to the
45;    glamboundary (when defined) by using the first line of glamt. if
46;    key_periodic=0 then in any case key_shift = 0.
47;
48; @keyword STRCALLING a string containing the calling command used to call
49;    computegrid (this is used by xxx.pro)
50;
51; @keyword STRIDE {default=key_stride}
52;    a 3 elements vector to specify the stride in x, y, z direction.
53;    The resulting value will be stored in the common (cm_4mesh) variable
54;    key_stride
55;
56; @keyword _EXTRA used to pass your keywords to the created function.
57;
58; @uses cm_4mesh cm_4data cm_4cal
59;
60; @restrictions define and/or use common variables from
61;               cm_4mesh, cm_4data, cm_4cal
62;
63; @restrictions
64;
65;  ixminmesh,ixmaxmesh,iyminmesh,iymaxmesh,izminmesh,izmaxmesh must
66;  be defined febore calling ncdf_meshread. if some of those value
67;  are equal to -1 they will be automatically defined
68;
69; @history Sebastien Masson (smasson\@lodyc.jussieu.fr)
70;                      12/1999
71; July 2004, Sebastien Masson: Several modifications (micromeshmask,
72; clean partial steps, clean use of key_stride, automatic definition
73; of key_shift, ...)
74; Oct. 2004, Sebastien Masson: add PERIODIC and SHIFT
75; Aug. 2005, Sebastien Masson: some cleaning + english
76;
77; @version $Id$
78;
79;-
80;------------------------------------------------------------
81;------------------------------------------------------------
82;------------------------------------------------------------
83PRO ncdf_meshread, filename, GLAMBOUNDARY = glamboundary, CHECKDAT = checkdat $
84                  , ONEARTH = onearth, GETDIMENSIONS = getdimensions $
85                  , PERIODIC = periodic, SHIFT = shift, STRIDE = stride $
86                  , STRCALLING = strcalling, _EXTRA = ex
87;
88;---------------------------------------------------------
89;
90  compile_opt idl2, strictarrsubs
91;
92@cm_4mesh
93@cm_4data
94@cm_4cal
95  IF NOT keyword_set(key_forgetold) THEN BEGIN
96@updatenew
97@updatekwd
98  ENDIF
99;---------------------------------------------------------
100;
101  tempsun = systime(1)          ; for key_performance
102  IF keyword_set(CHECKDAT) THEN BEGIN
103    print, ' The keyword CHECKDAT has been suppressed (it could create bugs).'
104    print, ' Remove it from the call of ncdf_meshread'
105    print, ' Please use smallmeshmask.pro or micromeshmask.pro to create a'
106    print, ' meshmask that has manageable size'
107    return
108  ENDIF
109;-------------------------------------------------------
110; find meshfile name and open it!
111;-------------------------------------------------------
112; def of filename by default
113  IF n_params() EQ 0 then filename = 'meshmask.nc'
114  meshname = isafile(file = filename, iodirectory = iodir, _EXTRA = ex)
115  meshname = meshname[0]
116;
117  noticebase = xnotice('Reading file !C '+meshname+'!C ...')
118; if the meshmask is on tape archive ... get it back
119  IF !version.OS_FAMILY EQ 'unix' THEN spawn, '\file '+meshname+' > /dev/null'
120  cdfid = ncdf_open(meshname)
121  contient = ncdf_inquire(cdfid)
122;------------------------------------------------------------
123; dimensions
124;------------------------------------------------------------
125  ncdf_diminq, cdfid, 'x', name, jpiglo
126  ncdf_diminq, cdfid, 'y', name, jpjglo
127  listdims = strlowcase(ncdf_listdims(cdfid))
128  IF (where(listdims EQ 'z'))[0] NE -1 THEN ncdf_diminq, cdfid, 'z', name, jpkglo ELSE BEGIN
129    dimid = (where(strmid(listdims, 0, 5) EQ 'depth'))[0]
130    IF dimid NE -1 THEN ncdf_diminq, cdfid, dimid, name, jpkglo ELSE BEGIN
131      dummy = report('We could not find the vertical dimension..., its name must be z or start with depth')
132      stop
133    ENDELSE
134  ENDELSE
135;
136  if keyword_set(getdimensions) then begin
137    widget_control, noticebase, bad_id = nothing, /destroy
138    ncdf_close,  cdfid
139    return
140  endif
141;-------------------------------------------------------
142; check that all i[xyz]min[ax]mesh are well defined
143;-------------------------------------------------------
144  if n_elements(ixminmesh) EQ 0 THEN ixminmesh = 0
145  if n_elements(ixmaxmesh) EQ 0 then ixmaxmesh = jpiglo-1
146  if ixminmesh EQ -1 THEN ixminmesh = 0
147  IF ixmaxmesh EQ -1 then ixmaxmesh = jpiglo-1
148  if n_elements(iyminmesh) EQ 0 THEN iyminmesh = 0
149  IF n_elements(iymaxmesh) EQ 0 then iymaxmesh = jpjglo-1
150  if iyminmesh EQ -1 THEN iyminmesh = 0
151  IF iymaxmesh EQ -1 then iymaxmesh = jpjglo-1
152  if n_elements(izminmesh) EQ 0 THEN izminmesh = 0
153  IF n_elements(izmaxmesh) EQ 0 then izmaxmesh = jpkglo-1
154  if izminmesh EQ -1 THEN izminmesh = 0
155  IF izmaxmesh EQ -1 then izmaxmesh = jpkglo-1
156; definition of jpi,jpj,jpj
157  jpi    = long(ixmaxmesh-ixminmesh+1)
158  jpj    = long(iymaxmesh-iyminmesh+1)
159  jpk    = long(izmaxmesh-izminmesh+1)
160;-------------------------------------------------------
161; check onearth and its consequences
162;-------------------------------------------------------
163  IF n_elements(onearth) EQ 0 THEN key_onearth = 1 $
164  ELSE key_onearth = keyword_set(onearth)
165  IF NOT key_onearth THEN BEGIN
166    periodic = 0
167    shift = 0
168  ENDIF
169;-------------------------------------------------------
170; automatic definition of key_periodic
171;-------------------------------------------------------
172  IF n_elements(periodic) EQ 0 THEN BEGIN
173    IF jpi GT 1 THEN BEGIN
174      varinq = ncdf_varinq(cdfid, 'glamt')
175      CASE varinq.ndims OF
176        2:ncdf_varget, cdfid, 'glamt', xaxis $
177                       , offset = [ixminmesh, iyminmesh], count = [jpi, 1]
178        3:ncdf_varget, cdfid, 'glamt', xaxis $
179                       , offset = [ixminmesh, iyminmesh, 0], count = [jpi, 1, 1]
180        4:ncdf_varget, cdfid, 'glamt', xaxis $
181                       , offset = [ixminmesh, iyminmesh, 0, 0], count = [jpi, 1, 1, 1]
182      ENDCASE
183      xaxis = (xaxis+720) MOD 360
184      xaxis = xaxis[sort(xaxis)]
185      key_periodic = (xaxis[jpi-1]+2*(xaxis[jpi-1]-xaxis[jpi-2])) $
186                     GE (xaxis[0]+360)
187    ENDIF ELSE key_periodic = 0
188  ENDIF ELSE key_periodic = keyword_set(periodic)
189;-------------------------------------------------------
190; automatic definition of key_shift
191;-------------------------------------------------------
192  IF n_elements(shift) EQ 0 THEN BEGIN
193    key_shift = long(testvar(var = key_shift))
194;  key_shift will be defined according to the first line of glamt.
195    if keyword_set(glamboundary) AND jpi GT 1 AND key_periodic EQ 1 $
196    THEN BEGIN
197      varinq = ncdf_varinq(cdfid, 'glamt')
198      CASE varinq.ndims OF
199        2:ncdf_varget, cdfid, 'glamt', xaxis $
200                       , offset = [ixminmesh, iyminmesh], count = [jpi, 1]
201        3:ncdf_varget, cdfid, 'glamt', xaxis $
202                       , offset = [ixminmesh, iyminmesh, 0], count = [jpi, 1, 1]
203        4:ncdf_varget, cdfid, 'glamt', xaxis $
204                       , offset = [ixminmesh, iyminmesh, 0, 0], count = [jpi, 1, 1, 1]
205      ENDCASE
206; xaxis between glamboundary[0] and glamboundary[1]
207      xaxis = xaxis MOD 360
208      smaller = where(xaxis LT glamboundary[0])
209      if smaller[0] NE -1 then xaxis[smaller] = xaxis[smaller]+360
210      bigger = where(xaxis GE glamboundary[1])
211      if bigger[0] NE -1 then xaxis[bigger] = xaxis[bigger]-360
212;
213      key_shift = (where(xaxis EQ min(xaxis)))[0]
214      IF key_shift NE 0 THEN BEGIN
215        key_shift = jpi-key_shift
216        xaxis = shift(xaxis, key_shift)
217      ENDIF
218;
219      IF array_equal(sort(xaxis), lindgen(jpi)) NE 1 THEN BEGIN
220        print, 'the x axis (1st line of glamt) is not sorted in the inceasing order after the automatic definition of key_shift'
221        print, 'please use the keyword shift (and periodic) to suppress the automatic definition of key_shift (and key_periodic) and define by hand a more suitable value...'
222        widget_control, noticebase, bad_id = nothing, /destroy
223        return
224      ENDIF
225;
226    ENDIF ELSE key_shift = 0
227  ENDIF ELSE key_shift = long(shift)*(key_periodic EQ 1)
228;-------------------------------------------------------
229; check key_stride and related things
230;-------------------------------------------------------
231  if n_elements(stride) eq 3 then key_stride = stride
232  if n_elements(key_stride) LE 2 then key_stride = [1, 1, 1]
233  key_stride = 1l > long(key_stride)
234  IF total(key_stride) NE 3  THEN BEGIN
235    IF key_shift NE 0 THEN BEGIN
236; for explanation, see header of read_ncdf_varget.pro
237      jpiright = key_shift
238      jpileft = jpi - key_shift - ( (key_stride[0]-1)-((key_shift-1) MOD key_stride[0]) )
239      jpi = ((jpiright-1)/key_stride[0]+1) + ((jpileft-1)/key_stride[0]+1)
240    ENDIF ELSE jpi = (jpi-1)/key_stride[0]+1
241    jpj = (jpj-1)/key_stride[1]+1
242    jpk = (jpk-1)/key_stride[2]+1
243  ENDIF
244;-------------------------------------------------------
245; default definitions to be able to use read_ncdf_varget
246;-------------------------------------------------------
247; default definitions to be able to use read_ncdf_varget
248  ixmindtasauve = testvar(var = ixmindta)
249  iymindtasauve = testvar(var = iymindta)
250  izmindtasauve = testvar(var = izmindta)
251;
252  ixmindta = 0l
253  iymindta = 0l
254  izmindta = 0l
255;
256  jpt = 1
257  time = 1
258  firsttps = 0
259;
260  firstx = 0
261  lastx = jpi-1
262  firsty = 0
263  lasty = jpj-1
264  firstz = 0
265  lastz = jpk-1
266  nx = jpi
267  ny = jpj
268  nz = 1
269  izminmeshsauve = izminmesh
270  izminmesh = 0
271;-------------------------------------------------------
272; 2d arrays:
273;-------------------------------------------------------
274; list the 2d variables that must be read
275  namevar = ['glamt', 'glamu', 'glamv', 'glamf' $
276             , 'gphit', 'gphiu', 'gphiv', 'gphif' $
277             , 'e1t', 'e1u', 'e1v', 'e1f' $
278             , 'e2t', 'e2u', 'e2v', 'e2f']
279; for the variables related to the partial steps
280  allvarname =  ncdf_listvars(cdfid)
281  IF (where(allvarname EQ 'hdept'))[0] NE -1 THEN BEGIN
282    key_partialstep = 1
283    namevar = [namevar, 'hdept', 'hdepw']
284  ENDIF ELSE BEGIN
285    key_partialstep = 0
286    hdept = -1
287    hdepw = -1
288  ENDELSE
289; for compatibility with old versions of meshmask/partial steps
290  IF (where(allvarname EQ 'e3tp'))[0] NE -1 THEN $
291    namevar = [namevar, 'e3tp', 'e3wp'] ELSE BEGIN
292    e3t_ps = -1
293    e3w_ps = -1
294  ENDELSE
295  IF (where(allvarname EQ 'e3t_ps'))[0] NE -1 $
296  THEN namevar = [namevar, 'e3t_ps', 'e3w_ps' ]ELSE BEGIN
297    e3t_ps = -1
298    e3w_ps = -1
299  ENDELSE
300  IF (where(allvarname EQ 'e3u_ps'))[0] NE -1 $
301  THEN namevar = [namevar, 'e3u_ps', 'e3v_ps'] ELSE BEGIN
302    e3u_ps = -1
303    e3v_ps = -1
304  ENDELSE
305;
306; read all the 2d variables
307;
308  for i = 0, n_elements(namevar)-1 do begin
309    varcontient = ncdf_varinq(cdfid, namevar[i])
310    name = varcontient.name
311@read_ncdf_varget
312    command = namevar[i]+'=float(res)'
313    nothing = execute(command)
314  ENDFOR
315; for compatibility with old versions of meshmask/partial steps
316; change e3[tw]p to e3[tw]_ps
317  IF n_elements(e3tp) NE 0 THEN e3t_ps = temporary(e3tp)
318  IF n_elements(e3wp) NE 0 THEN e3w_ps = temporary(e3wp)
319; in the case of key_stride ne [1, 1, 1] redefine f points
320; coordinates: they must be in the middle of 3 T points
321  if key_stride[0] NE 1 OR key_stride[1] NE 1 then BEGIN
322; we must recompute glamf and gphif...
323    IF jpi GT 1 THEN BEGIN
324      if (keyword_set(key_onearth) AND keyword_set(xnotsorted)) $
325        OR (keyword_set(key_periodic) AND key_irregular) then BEGIN
326        stepxf = (glamt + 720) MOD 360
327        stepxf = shift(stepxf, -1, -1) - stepxf
328        stepxf = [ [[stepxf]], [[stepxf + 360]], [[stepxf - 360]] ]
329        stepxf = min(abs(stepxf), dimension = 3)
330        IF NOT keyword_set(key_periodic) THEN $
331          stepxf[jpi-1, *] = stepxf[jpi-2, *]
332      ENDIF ELSE BEGIN
333        stepxf = shift(glamt, -1, -1) - glamt
334        IF keyword_set(key_periodic) THEN $
335          stepxf[jpi-1, *] = 360 + stepxf[jpi-1, *] $
336        ELSE stepxf[jpi-1, *] = stepxf[jpi-2, *]
337      ENDELSE
338      IF jpj GT 1 THEN BEGIN
339        stepxf[*, jpj-1] = stepxf[*, jpj-2]
340        stepxf[jpi-1, jpj-1] = stepxf[jpi-2, jpj-2]
341      ENDIF
342      glamf = glamt + 0.5 * stepxf
343    ENDIF ELSE glamf = glamt + 0.5
344    IF jpj GT 1 THEN BEGIN
345; we must compute stepyf: y distance between T(i,j) T(i+1,j+1)
346      stepyf = shift(gphit, -1, -1) - gphit
347      stepyf[*, jpj-1] = stepyf[*, jpj-2]
348      IF jpi GT 1 THEN BEGIN
349        if NOT keyword_set(key_periodic) THEN $
350          stepyf[jpi-1, *] = stepyf[jpi-2, *]
351        stepyf[jpi-1, jpj-1] = stepyf[jpi-2, jpj-2]
352      ENDIF
353      gphif = gphit + 0.5 * stepyf
354    ENDIF ELSE gphif = gphit + 0.5
355  ENDIF
356;-------------------------------------------------------
357; 3d arrays:
358;-------------------------------------------------------
359  nz = jpk
360  izminmesh = izminmeshsauve
361;
362  listdims = ncdf_listdims(cdfid)
363  micromask = (where(listdims EQ 'y_m'))[0]
364;
365  varcontient = ncdf_varinq(cdfid, 'tmask')
366  name = varcontient.name
367  IF micromask NE -1 THEN BEGIN
368; keep original values
369    iyminmeshtrue = iyminmesh
370    key_stridetrue = key_stride
371    yyy1 = firsty*key_stridetrue[1]+iyminmeshtrue
372    yyy2 = lasty*key_stridetrue[1]+iyminmeshtrue
373; the mask is stored as the bit values of the byte array (along the y
374; dimension, see micromeshmask.pro)...
375; we must modify several parameters...
376    iyminmesh = 0L
377    firsty = yyy1/8
378    lasty = yyy2/8
379    ny = lasty-firsty+1
380    key_stride = [key_stride[0], 1, key_stride[2]]
381@read_ncdf_varget
382    tmask = bytarr(jpi, jpj, jpk)
383; now we must get back the mask
384; loop on the level to save memory (the loop is short and, thus,
385; should be fast enough)
386    FOR k = 0, jpk-1 DO BEGIN
387      zzz = transpose(res[*, *, k])
388      zzz = reform(binary(zzz), 8*ny, nx, /over)
389      zzz = transpose(temporary(zzz))
390      zzz = zzz[*, yyy1 MOD 8: 8*ny - 8 + yyy2 MOD 8]
391      IF key_stridetrue[1] NE 1 THEN BEGIN
392;        IF float(strmid(!version.release,0,3)) LT 5.6 THEN BEGIN
393        nnny = (size(zzz))[2]
394        yind = key_stridetrue[1]*lindgen((nnny-1)/key_stridetrue[1]+1)
395        tmask[*, *, k] = temporary(zzz[*, yind])
396;        ENDIF ELSE tmask[*, *, k] = temporary(zzz[*, 0:*:key_stridetrue[1]])
397      ENDIF ELSE tmask[*, *, k] = temporary(zzz)
398    ENDFOR
399  ENDIF ELSE BEGIN
400@read_ncdf_varget
401    tmask = byte(res)
402  ENDELSE
403; boudary conditions used to compute umask.
404  varcontient = ncdf_varinq(cdfid, 'umask')
405  name = varcontient.name
406  nx = 1L
407  firstx = jpi-1
408  lastx = jpi-1
409  IF micromask NE -1 THEN BEGIN
410@read_ncdf_varget
411    umaskred = reform(binary(res), 8*ny, jpk, /over)
412    umaskred = umaskred[yyy1 MOD 8: 8*ny - 8 + yyy2 MOD 8, *]
413    IF key_stridetrue[1] NE 1 THEN umaskred = temporary(umaskred[yind, *])
414  ENDIF ELSE BEGIN
415@read_ncdf_varget
416    umaskred = reform(byte(res), /over)
417  ENDELSE
418; boudary conditions used to compute fmask (1).
419  varcontient = ncdf_varinq(cdfid, 'fmask')
420  name = varcontient.name
421  IF micromask NE -1 THEN BEGIN
422@read_ncdf_varget
423    fmaskredy = reform(binary(res), 8*ny, jpk, /over)
424    fmaskredy = fmaskredy[yyy1 MOD 8: 8*ny - 8 + yyy2 MOD 8, *]
425    IF key_stridetrue[1] NE 1 THEN fmaskredy = temporary(fmaskredy[yind, *])
426  ENDIF ELSE BEGIN
427@read_ncdf_varget
428    fmaskredy = reform(byte(res), /over)
429    fmaskredy = temporary(fmaskredy) MOD 2
430  ENDELSE
431; boudary conditions used to compute vmask
432  varcontient = ncdf_varinq(cdfid, 'vmask')
433  name = varcontient.name
434  nx = jpi
435  firstx = 0L
436  lastx = jpi-1L
437  ny = 1L
438  firsty = jpj-1
439  lasty = jpj-1
440  IF micromask NE -1 THEN BEGIN
441    yyy1 = firsty*key_stridetrue[1]+iyminmeshtrue
442    yyy2 = lasty*key_stridetrue[1]+iyminmeshtrue
443    iyminmesh = 0L
444    firsty = yyy1/8
445    lasty = yyy2/8
446    ny = lasty-firsty+1
447@read_ncdf_varget
448    IF jpk EQ 1 THEN res = reform(res, jpi, 1, jpk, /over)
449    vmaskred = transpose(temporary(res), [1, 0, 2])
450    vmaskred = reform(binary(vmaskred), 8*ny, nx, nz, /over)
451    vmaskred = transpose(temporary(vmaskred), [1, 0, 2])
452    vmaskred = reform(vmaskred[*, yyy1 MOD 8: 8*ny - 8 + yyy2 MOD 8, *])
453  ENDIF ELSE BEGIN
454@read_ncdf_varget
455    vmaskred = reform(byte(res), /over)
456  ENDELSE
457; boudary conditions used to compute fmask (2).
458  varcontient = ncdf_varinq(cdfid, 'fmask')
459  name = varcontient.name
460  IF micromask NE -1 THEN BEGIN
461@read_ncdf_varget
462    IF jpk EQ 1 THEN res = reform(res, jpi, 1, jpk, /over)
463    fmaskredx = transpose(temporary(res), [1, 0, 2])
464    fmaskredx = reform(binary(fmaskredx), 8*ny, nx, nz, /over)
465    fmaskredx = transpose(temporary(fmaskredx), [1, 0, 2])
466    fmaskredx = reform(fmaskredx[*, yyy1 MOD 8: 8*ny - 8 + yyy2 MOD 8, *])
467;
468    iyminmesh = iyminmeshtrue
469    key_stride = key_stridetrue
470  ENDIF ELSE BEGIN
471@read_ncdf_varget
472    fmaskredx = reform(byte(res), /over)
473    fmaskredx = fmaskredx MOD 2
474  ENDELSE
475;-------------------------------------------------------
476; 1d arrays
477;-------------------------------------------------------
478  namevar = ['e3t', 'e3w', 'gdept', 'gdepw']
479  for i = 0, n_elements(namevar)-1 do begin
480    varcontient = ncdf_varinq(cdfid, namevar[i])
481    CASE n_elements(varcontient.dim) OF
482      4:BEGIN
483        command = 'ncdf_varget,cdfid,namevar[i],'+namevar[i] $
484                   +',offset = [0,0,izminmesh,0], count = [1,1,jpk,1]'
485        if key_stride[2] NE 1 then command = command+', stride=[1,1,key_stride[2],1]'
486      END
487      2:BEGIN
488        command = 'ncdf_varget,cdfid,namevar[i],'+namevar[i] $
489                   +',offset = [izminmesh,0], count = [jpk,1]'
490        if key_stride[2] NE 1 then command = command+', stride=key_stride[2]'
491      END
492      1:BEGIN
493        command = 'ncdf_varget,cdfid,namevar[i],'+namevar[i] $
494                   +',offset = [izminmesh], count = [jpk]'
495        if key_stride[2] NE 1 then command = command+', stride=key_stride[2]'
496      END
497    ENDCASE
498    nothing = execute(command)
499    command = namevar[i]+'=float('+namevar[i]+')'
500    nothing = execute(command)
501    command = 'if size('+namevar[i]+', /n_dimension) gt 0 then '+namevar[i]+' = reform('+namevar[i]+', /over)'
502    nothing = execute(command)
503  ENDFOR
504;-------------------------------------------------------
505  ncdf_close,  cdfid
506;-------------------------------------------------------
507; Apply Glamboudary
508;-------------------------------------------------------
509  if keyword_set(glamboundary) AND key_onearth then BEGIN
510    if glamboundary[0] NE glamboundary[1] then BEGIN
511      glamt = glamt MOD 360
512      smaller = where(glamt LT glamboundary[0])
513      if smaller[0] NE -1 then glamt[smaller] = glamt[smaller]+360
514      bigger = where(glamt GE glamboundary[1])
515      if bigger[0] NE -1 then glamt[bigger] = glamt[bigger]-360
516      glamu = glamu MOD 360
517      smaller = where(glamu LT glamboundary[0])
518      if smaller[0] NE -1 then glamu[smaller] = glamu[smaller]+360
519      bigger = where(glamu GE glamboundary[1])
520      if bigger[0] NE -1 then glamu[bigger] = glamu[bigger]-360
521      glamv = glamv MOD 360
522      smaller = where(glamv LT glamboundary[0])
523      if smaller[0] NE -1 then glamv[smaller] = glamv[smaller]+360
524      bigger = where(glamv GE glamboundary[1])
525      if bigger[0] NE -1 then glamv[bigger] = glamv[bigger]-360
526      glamf = glamf MOD 360
527      smaller = where(glamf LT glamboundary[0])
528      if smaller[0] NE -1 then glamf[smaller] = glamf[smaller]+360
529      bigger = where(glamf GE glamboundary[1])
530      if bigger[0] NE -1 then glamf[bigger] = glamf[bigger]-360
531      toosmall = where(glamu EQ glamboundary[0])
532      IF toosmall[0] NE -1 THEN glamu[toosmall] = glamu[toosmall] + 360
533      toosmall = where(glamf EQ glamboundary[0])
534      IF toosmall[0] NE -1 THEN glamf[toosmall] = glamf[toosmall] + 360
535    endif
536  endif
537;-------------------------------------------------------
538; make sure we do have 2d arrays when jpj eq 1
539;-------------------------------------------------------
540  IF jpj EQ 1 THEN BEGIN
541    glamt = reform(glamt, jpi, jpj, /over)
542    gphit = reform(gphit, jpi, jpj, /over)
543    e1t = reform(e1t, jpi, jpj, /over)
544    e2t = reform(e2t, jpi, jpj, /over)
545    glamu = reform(glamu, jpi, jpj, /over)
546    gphiu = reform(gphiu, jpi, jpj, /over)
547    e1u = reform(e1u, jpi, jpj, /over)
548    e2u = reform(e2u, jpi, jpj, /over)
549    glamv = reform(glamv, jpi, jpj, /over)
550    gphiv = reform(gphiv, jpi, jpj, /over)
551    e1v = reform(e1v, jpi, jpj, /over)
552    e2v = reform(e2v, jpi, jpj, /over)
553    glamf = reform(glamf, jpi, jpj, /over)
554    gphif = reform(gphif, jpi, jpj, /over)
555    e1f = reform(e1f, jpi, jpj, /over)
556    e2f = reform(e2f, jpi, jpj, /over)
557    IF keyword_set(key_partialstep) THEN BEGIN
558      hdept = reform(hdept, jpi, jpj, /over)
559      hdepw = reform(hdepw, jpi, jpj, /over)
560      e3t_ps = reform(e3t_ps, jpi, jpj, /over)
561      e3w_ps = reform(e3w_ps, jpi, jpj, /over)
562    ENDIF
563  ENDIF
564;-------------------------------------------------------
565  ixmindta = ixmindtasauve
566  iymindta = iymindtasauve
567  izmindta = izmindtasauve
568;-------------------------------------------------------
569  widget_control, noticebase, bad_id = nothing, /destroy
570;
571  key_yreverse = 0
572  key_zreverse = 0
573  key_gridtype = 'c'
574;
575;====================================================
576; grid parameters used by xxx
577;====================================================
578;
579  IF NOT keyword_set(strcalling) THEN BEGIN
580    IF n_elements(ccmeshparameters) EQ 0 THEN strcalling = 'ncdf_meshread' $
581    ELSE strcalling = ccmeshparameters.filename
582  ENDIF
583  IF n_elements(glamt) GE 2 THEN BEGIN
584    glaminfo = moment(glamt)
585    IF finite(glaminfo[2]) EQ 0 THEN glaminfo = glaminfo[0:1]
586    gphiinfo = moment(gphit)
587    IF finite(gphiinfo[2]) EQ 0 THEN gphiinfo = gphiinfo[0:1]
588  ENDIF ELSE BEGIN
589    glaminfo = glamt
590    gphiinfo = gphit
591  ENDELSE
592  ccmeshparameters = {filename:strcalling  $
593          , glaminfo:float(string(glaminfo, format = '(E11.4)')) $
594          , gphiinfo:float(string(gphiinfo, format = '(E11.4)')) $
595          , jpiglo:jpiglo, jpjglo:jpjglo, jpkglo:jpkglo $
596          , jpi:jpi, jpj:jpj, jpk:jpk $
597          , ixminmesh:ixminmesh, ixmaxmesh:ixmaxmesh $
598          , iyminmesh:iyminmesh, iymaxmesh:iymaxmesh $
599          , izminmesh:izminmesh, izmaxmesh:izmaxmesh $
600          , key_shift:key_shift, key_periodic:key_periodic $
601          , key_stride:key_stride, key_gridtype:key_gridtype $
602          , key_yreverse:key_yreverse, key_zreverse:key_zreverse $
603          , key_partialstep:key_partialstep, key_onearth:key_onearth}
604;
605  if keyword_set(key_performance) THEN $
606    print, 'time ncdf_meshread', systime(1)-tempsun
607
608;-------------------------------------------------------
609   @updateold
610;-------------------------------------------------------
611   return
612 end
Note: See TracBrowser for help on using the repository browser.