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

Last change on this file since 134 was 134, checked in by navarro, 18 years ago

change *.pro file properties (del eof-style, del executable, set keywords Id

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