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

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

header improvements : type of parameters and keywords, default values, spell checking + idldoc assistant (IDL online_help)

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