source: trunk/SRC/Grid/ncdf_meshroms.pro @ 273

Last change on this file since 273 was 273, checked in by smasson, 17 years ago

bugfix related to revision 271

  • Property svn:keywords set to Id
File size: 19.9 KB
Line 
1;+
2;
3; @file_comments
4; read NetCDF grid file created by ROMS
5;
6; @categories
7; Grid
8;
9; @examples
10; IDL> ncdf_meshroms [,' filename']
11;
12; @param filename {in}{optional}{default='roms_grd.nc'}{type=scalar string}
13;    Name of the meshmask file to read. If this name does not contain any "/"
14;    and if iodirectory keyword is not specify, then the common variable
15;    iodir will be used to define the mesh file path.
16;
17; @keyword GLAMBOUNDARY {default=those defined in the file}{type=2 elements vector}
18;    Longitude boundaries that should be used to visualize the data.
19;      lon2 > lon1
20;      lon2 - lon1 le 360
21;    By default, the common (cm_4mesh) variable key_shift will be automatically
22;    defined according to GLAMBOUNDARY.
23;
24; @keyword ONEARTH {default=1}{type=scalar: 0 or 1}
25;    Force the manual definition of data localization on the earth or not
26;       0) if the data are not on the earth
27;       1) if the data are on earth (in that case we can for example use
28;          the labels 'longitude', 'latitude' in plots).
29;    The resulting value will be stored in the common (cm_4mesh) variable key_onearth
30;    ONEARTH = 0 forces PERIODIC = 0, SHIFT = 0 and is cancelling GLAMBOUNDARY
31;
32; @keyword GETDIMENSIONS {default=0}{type=scalar: 0 or 1}
33;    Activate this keywords if you only want to know the dimension
34;    of the domain stored in the mesh file. This dimension will be
35;    defined in jpiglo, jpjglo, jpkglo (cm_4mesh common variables)
36;
37; @keyword PERIODIC {default=computed by using the first line of glamt}{type=scalar: 0 or 1}
38;    Force the manual definition of the grid zonal periodicity.
39;    The resulting value will be stored in the common (cm_4mesh) variable key_periodic
40;    PERIODIC = 0 forces SHIFT = 0
41;
42; @keyword NRHO {default=1}{type=scalar}
43;    Specify the number of rho level that contain the data we want to explore.
44;    This is mainly useful when using <pro>xxx</pro> to get access to the deeper levers and vertical sections.
45;
46; @keyword SHIFT {default=computed according to glamboundary}{type=scalar}
47;    Force the manual definition of the zonal shift that must be apply to the data.
48;    The resulting value will be stored in the common (cm_4mesh) variable key_shift
49;    Note that if key_periodic=0 then in any case key_shift = 0.
50;
51; @keyword STRCALLING {type=scalar string}
52;    the calling command used to call <pro>computegrid</pro> (this is used by <pro>xxx</pro>)
53;
54; @keyword STRIDE {default=[1, 1, 1]}{type=3 elements vector}
55;    Specify the stride in x, y and z direction. The resulting
56;    value will be stored in the common (cm_4mesh) variable key_stride
57;
58; @keyword _EXTRA
59; Used to pass keywords to <pro>isafile</pro>
60;
61; @uses
62; cm_4mesh
63; cm_4data
64; cm_4cal
65;
66; @restrictions
67; ixminmesh, ixmaxmesh, iyminmesh, iymaxmesh, izminmesh, izmaxmesh must
68; be defined before calling <pro>ncdf_meshread</pro>. If some of those values
69; are equal to -1 they will be automatically defined
70;
71; In the original ROMS grid, if F grid has (jpi,jpj) points then T
72; grid will have (jpi+1,jpj+1) points, U grid will have (jpi,jpj+1)
73; points and V grid will have (jpi+1,jpj) points.
74; By default C-grid used in this package needs the same number of
75; points for T,U,V and F grid, with a T point at the bottom left
76; corner of the grid. We therefore ignore the last column of T and
77; V points and the last line of T and U points.
78;
79; Scale factors are computed using the distance between the points
80; (which is not the exact definition for irregular grid).
81;
82; @history
83; Sebastien Masson (smasson\@lodyc.jussieu.fr) September 2006
84;
85; @version
86; $Id$
87;
88;-
89;
90PRO ncdf_meshroms, filename, NRHO = nrho, GLAMBOUNDARY = glamboundary $
91                  , ONEARTH = onearth, GETDIMENSIONS = getdimensions $
92                  , PERIODIC = periodic, SHIFT = shift, STRIDE = stride $
93                  , STRCALLING = strcalling, _EXTRA = ex
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;-------------------------------------------------------
108; find meshfile name and open it!
109;-------------------------------------------------------
110; def of filename by default
111  IF n_params() EQ 0 then filename = 'roms_grd.nc'
112  meshname = isafile(file = filename, iodirectory = iodir, _EXTRA = ex)
113  meshname = meshname[0]
114;
115  noticebase = xnotice('Reading file !C '+meshname+'!C ...')
116; if the meshmask is on tape archive ... get it back
117  IF !version.OS_FAMILY EQ 'unix' THEN spawn, '\file '+meshname+' > /dev/null'
118  cdfid = ncdf_open(meshname)
119  inq = ncdf_inquire(cdfid)
120;------------------------------------------------------------
121; dimensions
122;------------------------------------------------------------
123  ncdf_diminq, cdfid, 'xi_rho', name, jpiglo
124  ncdf_diminq, cdfid, 'eta_rho', name, jpjglo
125  IF n_elements(nrho) NE 0 THEN jpkglo = long(nrho[0]) $
126    ELSE jpkglo = 1L
127;
128  if keyword_set(getdimensions) then begin
129    widget_control, noticebase, bad_id = nothing, /destroy
130    ncdf_close,  cdfid
131    return
132  endif
133;-------------------------------------------------------
134; check that all i[xyz]min[ax]mesh are well defined
135;-------------------------------------------------------
136  if n_elements(ixminmesh) EQ 0 THEN ixminmesh = 0
137  if n_elements(ixmaxmesh) EQ 0 then ixmaxmesh = jpiglo-1
138  if ixminmesh EQ -1 THEN ixminmesh = 0
139  IF ixmaxmesh EQ -1 then ixmaxmesh = jpiglo-1
140  if n_elements(iyminmesh) EQ 0 THEN iyminmesh = 0
141  IF n_elements(iymaxmesh) EQ 0 then iymaxmesh = jpjglo-1
142  if iyminmesh EQ -1 THEN iyminmesh = 0
143  IF iymaxmesh EQ -1 then iymaxmesh = jpjglo-1
144  if n_elements(izminmesh) EQ 0 THEN izminmesh = 0
145  IF n_elements(izmaxmesh) EQ 0 then izmaxmesh = jpkglo-1
146  if izminmesh EQ -1 THEN izminmesh = 0
147  IF izmaxmesh EQ -1 then izmaxmesh = jpkglo-1
148; definition of jpi,jpj,jpj
149  jpi = long(ixmaxmesh-ixminmesh+1)
150  jpj = long(iymaxmesh-iyminmesh+1)
151  jpk = long(izmaxmesh-izminmesh+1)
152;-------------------------------------------------------
153; check onearth and its consequences
154;-------------------------------------------------------
155  IF n_elements(onearth) EQ 0 THEN key_onearth = 1 $
156  ELSE key_onearth = keyword_set(onearth)
157  IF NOT key_onearth THEN BEGIN
158    periodic = 0
159    shift = 0
160  ENDIF
161;-------------------------------------------------------
162; automatic definition of key_periodic
163;-------------------------------------------------------
164  IF n_elements(periodic) EQ 0 THEN BEGIN
165    IF jpi GT 1 THEN BEGIN
166      ncdf_varget, cdfid, 'lon_rho', xaxis $
167                   , offset = [ixminmesh, iyminmesh], count = [jpi, 1]
168      xaxis = (xaxis+720) MOD 360
169      xaxis = xaxis[sort(xaxis)]
170      key_periodic = (xaxis[jpi-1]+2*(xaxis[jpi-1]-xaxis[jpi-2])) $
171                     GE (xaxis[0]+360)
172    ENDIF ELSE key_periodic = 0
173  ENDIF ELSE key_periodic = keyword_set(periodic)
174;-------------------------------------------------------
175; automatic definition of key_shift
176;-------------------------------------------------------
177  IF n_elements(shift) EQ 0 THEN BEGIN
178    key_shift = long(testvar(var = key_shift))
179;  key_shift will be defined according to the first line of glamt.
180    if keyword_set(glamboundary) AND jpi GT 1 AND key_periodic EQ 1 $
181    THEN BEGIN
182      ncdf_varget, cdfid, 'lon_rho', xaxis $
183                   , offset = [ixminmesh, iyminmesh], count = [jpi, 1]
184; xaxis between glamboundary[0] and glamboundary[1]
185      xaxis = xaxis MOD 360
186      smaller = where(xaxis LT glamboundary[0])
187      if smaller[0] NE -1 then xaxis[smaller] = xaxis[smaller]+360
188      bigger = where(xaxis GE glamboundary[1])
189      if bigger[0] NE -1 then xaxis[bigger] = xaxis[bigger]-360
190;
191      key_shift = (where(xaxis EQ min(xaxis)))[0]
192      IF key_shift NE 0 THEN BEGIN
193        key_shift = jpi-key_shift
194        xaxis = shift(xaxis, key_shift)
195      ENDIF
196;
197      IF array_equal(sort(xaxis), lindgen(jpi)) NE 1 THEN BEGIN
198        ras = report (['the x axis (1st line of glamt) is not sorted in the increasing order after the automatic definition of key_shift', $
199        '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...'])
200        widget_control, noticebase, bad_id = nothing, /destroy
201        return
202      ENDIF
203;
204    ENDIF ELSE key_shift = 0
205  ENDIF ELSE key_shift = long(shift)*(key_periodic EQ 1)
206;-------------------------------------------------------
207; check key_stride and related things
208;-------------------------------------------------------
209  if n_elements(stride) eq 3 then key_stride = stride
210  if n_elements(key_stride) LE 2 then key_stride = [1, 1, 1]
211  key_stride = 1l > long(key_stride)
212  IF total(key_stride) NE 3  THEN BEGIN
213    IF key_shift NE 0 THEN BEGIN
214; for explanation, see header of read_ncdf_varget.pro
215      jpiright = key_shift
216      jpileft = jpi - key_shift - ( (key_stride[0]-1)-((key_shift-1) MOD key_stride[0]) )
217      jpi = ((jpiright-1)/key_stride[0]+1) + ((jpileft-1)/key_stride[0]+1)
218    ENDIF ELSE jpi = (jpi-1)/key_stride[0]+1
219    jpj = (jpj-1)/key_stride[1]+1
220    jpk = (jpk-1)/key_stride[2]+1
221  ENDIF
222;-------------------------------------------------------
223; for the variables related to the partial steps
224;-------------------------------------------------------
225  key_partialstep = 0
226  hdept = -1
227  hdepw = -1
228;-------------------------------------------------------
229; default definitions to be able to use read_ncdf_varget
230;-------------------------------------------------------
231; default definitions to be able to use read_ncdf_varget
232  ixmindtasauve = testvar(var = ixmindta)
233  iymindtasauve = testvar(var = iymindta)
234  izmindtasauve = testvar(var = izmindta)
235;
236  ixmindta = 0l
237  iymindta = 0l
238  izmindta = 0l
239;
240  jpt = 1
241  time = 1
242  firsttps = 0
243;
244  firstx = 0
245  lastx = jpi-1
246  firsty = 0
247  lasty = jpj-1
248  firstz = 0
249  lastz = jpk-1
250  nx = jpi
251  ny = jpj
252  nz = 1
253  izminmeshsauve = izminmesh
254  izminmesh = 0
255;
256  key_yreverse = 0
257  key_zreverse = 1
258  key_gridtype = 'c'
259;-------------------------------------------------------
260; 2d arrays:
261;-------------------------------------------------------
262; list the 2d variables that must be read
263  namebase  = ['lon_', 'lat_', 'mask_', 'x_', 'y_']
264  namebase2 = ['glam', 'gphi', 'mask' , 'd1', 'd2']
265;
266; read all grid T variables
267;
268  for i = 0, n_elements(namebase)-1 do begin
269    varinq = ncdf_varinq(cdfid, namebase[i]+'rho')
270    name = varinq.name
271@read_ncdf_varget
272    command = namebase2[i]+'t = float(temporary(res))'
273    nothing = execute(command)
274  ENDFOR
275  d1t = 1.e3*(shift(d1t, -1, 0) - d1t)
276  d2t = 1.e3*(shift(d2t, 0, -1) - d2t)
277  for i = 0, n_elements(namebase2)-1 do begin
278    command = namebase2[i]+'t = '+namebase2[i]+'t[0:jpi-2, 0:jpj-2]'
279    nothing = execute(command)
280  ENDFOR
281  tmask = byte(temporary(maskt))
282  IF jpk GT 1 THEN tmask = reform(tmask[*]#replicate(1b, jpk), jpi-1, jpj-1, jpk, /overwrite)
283  e1u = temporary(d1t)
284  e2v = temporary(d2t)
285; h: Final bathymetry at RHO-points
286    varinq = ncdf_varinq(cdfid, 'h')
287    name = varinq.name
288@read_ncdf_varget
289    hroms = float(temporary(res))
290    hroms = hroms[0:jpi-2, 0:jpj-2]
291;
292; read all grid U variables
293;
294  jpiglo = jpiglo - 1
295  jpi = jpi - 1
296  ixmaxmesh = ixmaxmesh - 1
297  firstx = 0
298  lastx = jpi-1
299  nx = jpi
300;
301  for i = 0, n_elements(namebase)-1 do begin
302    varinq = ncdf_varinq(cdfid, namebase[i]+'u')
303    name = varinq.name
304@read_ncdf_varget
305    command = namebase2[i]+'u = float(temporary(res))'
306    nothing = execute(command)
307  ENDFOR
308  tmpsave = 2. * 1.e3 * d1u[0, 0:jpj-2]
309  d1u = 1.e3*(shift(d1u, -1, 0) - d1u)
310  d2u = 1.e3*(shift(d2u, 0, -1) - d2u)
311  for i = 0, n_elements(namebase2)-1 do begin
312    command = namebase2[i]+'u = '+namebase2[i]+'u[*, 0:jpj-2]'
313    nothing = execute(command)
314  ENDFOR
315  umaskred = byte((temporary(masku))[jpi-1, *])
316  IF jpk GT 1 THEN umaskred = reform(umaskred[*]#replicate(1b, jpk), 1, jpj-1, jpk, /overwrite)
317  e1t = temporary(d1u)
318  e1t = shift(temporary(e1t), 1, 0)
319  e1t[0, *] = temporary(tmpsave)
320  e2f = temporary(d2u)
321;
322; read all grid V variables
323;
324  jpiglo = jpiglo + 1
325  jpi = jpi + 1
326  ixmaxmesh = ixmaxmesh + 1
327  firstx = 0
328  lastx = jpi-1
329  nx = jpi
330  jpjglo = jpjglo - 1
331  jpj = jpj - 1
332  iymaxmesh = iymaxmesh - 1
333  firsty = 0
334  lasty = jpj-1
335  ny = jpj
336;
337  for i = 0, n_elements(namebase)-1 do begin
338    varinq = ncdf_varinq(cdfid, namebase[i]+'v')
339    name = varinq.name
340@read_ncdf_varget
341    command = namebase2[i]+'v = float(temporary(res))'
342    nothing = execute(command)
343  ENDFOR
344  d1v = 1.e3*(shift(d1v, -1, 0) - d1v)
345  tmpsave = 2. * 1.e3 * d2v[0:jpi-2, 0]
346  d2v = 1.e3*(shift(d2v, 0, -1) - d2v)
347  for i = 0, n_elements(namebase2)-1 do begin
348    command = namebase2[i]+'v = '+namebase2[i]+'v[0:jpi-2, *]'
349    nothing = execute(command)
350  ENDFOR
351  vmaskred = byte((temporary(maskv))[*, jpj-1])
352  IF jpk GT 1 THEN vmaskred = reform(vmaskred[*]#replicate(1b, jpk), jpi-1, 1, jpk, /overwrite)
353  e1f = temporary(d1v)
354  e2t = temporary(d2v)
355  e2t = shift(temporary(e2t), 0, 1)
356  e2t[*, 0] = temporary(tmpsave)
357;
358; read all grid F variables
359;
360  jpiglo = jpiglo - 1
361  jpi = jpi - 1
362  ixmaxmesh = ixmaxmesh - 1
363  firstx = 0
364  lastx = jpi-1
365  nx = jpi
366;
367  for i = 0, n_elements(namebase)-1 do begin
368    varinq = ncdf_varinq(cdfid, namebase[i]+'psi')
369    name = varinq.name
370@read_ncdf_varget
371    command = namebase2[i]+'f = float(temporary(res))'
372    nothing = execute(command)
373  ENDFOR
374  tmpsave1 = 2. * 1.e3 * d1f[0, *]
375  d1f = 1.e3*(shift(d1f, -1, 0) - d1f)
376  tmpsave2 = 2. * 1.e3 * d2f[*, 0]
377  d2f = 1.e3*(shift(d2f, 0, -1) - d2f)
378  fmaskredy = byte(maskf[jpi-1, *])
379  IF jpk GT 1 THEN fmaskredy = reform(fmaskredy[*]#replicate(1b, jpk), 1, jpj, jpk, /overwrite)
380  fmaskredx = byte((temporary(maskf))[*, jpj-1])
381  IF jpk GT 1 THEN fmaskredx = reform(fmaskredx[*]#replicate(1b, jpk), jpi, 1, jpk, /overwrite)
382  e1v = temporary(d1f)
383  e1v = shift(temporary(e1v), 1, 0)
384  e1v[0, *] = temporary(tmpsave1)
385  e2u = temporary(d2f)
386  e2u = shift(temporary(e2u), 0, 1)
387  e2u[*, 0] = temporary(tmpsave2)
388;-------------------------------------------------------
389; in the case of key_stride ne [1, 1, 1] redefine f points
390; coordinates: they must be in the middle of 3 T points
391;-------------------------------------------------------
392  if key_stride[0] NE 1 OR key_stride[1] NE 1 then BEGIN
393; we must recompute glamf and gphif...
394    IF jpi GT 1 THEN BEGIN
395      if (keyword_set(key_onearth) AND keyword_set(xnotsorted)) $
396        OR (keyword_set(key_periodic) AND key_irregular) then BEGIN
397        stepxf = (glamt + 720) MOD 360
398        stepxf = shift(stepxf, -1, -1) - stepxf
399        stepxf = [ [[stepxf]], [[stepxf + 360]], [[stepxf - 360]] ]
400        stepxf = min(abs(stepxf), dimension = 3)
401        IF NOT keyword_set(key_periodic) THEN $
402          stepxf[jpi-1, *] = stepxf[jpi-2, *]
403      ENDIF ELSE BEGIN
404        stepxf = shift(glamt, -1, -1) - glamt
405        IF keyword_set(key_periodic) THEN $
406          stepxf[jpi-1, *] = 360 + stepxf[jpi-1, *] $
407        ELSE stepxf[jpi-1, *] = stepxf[jpi-2, *]
408      ENDELSE
409      IF jpj GT 1 THEN BEGIN
410        stepxf[*, jpj-1] = stepxf[*, jpj-2]
411        stepxf[jpi-1, jpj-1] = stepxf[jpi-2, jpj-2]
412      ENDIF
413      glamf = glamt + 0.5 * stepxf
414    ENDIF ELSE glamf = glamt + 0.5
415    IF jpj GT 1 THEN BEGIN
416; we must compute stepyf: y distance between T(i,j) T(i+1,j+1)
417      stepyf = shift(gphit, -1, -1) - gphit
418      stepyf[*, jpj-1] = stepyf[*, jpj-2]
419      IF jpi GT 1 THEN BEGIN
420        if NOT keyword_set(key_periodic) THEN $
421          stepyf[jpi-1, *] = stepyf[jpi-2, *]
422        stepyf[jpi-1, jpj-1] = stepyf[jpi-2, jpj-2]
423      ENDIF
424      gphif = gphit + 0.5 * stepyf
425    ENDIF ELSE gphif = gphit + 0.5
426  ENDIF
427;-------------------------------------------------------
428; 1d arrays
429;-------------------------------------------------------
430  gdept = findgen(jpk)
431  gdepw = findgen(jpk)
432  e3t = replicate(1., jpk)
433  e3w = replicate(1., jpk)
434;-------------------------------------------------------
435  ncdf_close, cdfid
436;-------------------------------------------------------
437; Apply Glamboudary
438;-------------------------------------------------------
439  if keyword_set(glamboundary) AND key_onearth then BEGIN
440    if glamboundary[0] NE glamboundary[1] then BEGIN
441      glamt = temporary(glamt) MOD 360
442      smaller = where(glamt LT glamboundary[0])
443      if smaller[0] NE -1 then glamt[smaller] = glamt[smaller]+360
444      bigger = where(glamt GE glamboundary[1])
445      if bigger[0] NE -1 then glamt[bigger] = glamt[bigger]-360
446      glamu = temporary(glamu) MOD 360
447      smaller = where(glamu LT glamboundary[0])
448      if smaller[0] NE -1 then glamu[smaller] = glamu[smaller]+360
449      bigger = where(glamu GE glamboundary[1])
450      if bigger[0] NE -1 then glamu[bigger] = glamu[bigger]-360
451      glamv = temporary(glamv) MOD 360
452      smaller = where(glamv LT glamboundary[0])
453      if smaller[0] NE -1 then glamv[smaller] = glamv[smaller]+360
454      bigger = where(glamv GE glamboundary[1])
455      if bigger[0] NE -1 then glamv[bigger] = glamv[bigger]-360
456      glamf = temporary(glamf) MOD 360
457      smaller = where(glamf LT glamboundary[0])
458      if smaller[0] NE -1 then glamf[smaller] = glamf[smaller]+360
459      bigger = where(glamf GE glamboundary[1])
460      if bigger[0] NE -1 then glamf[bigger] = glamf[bigger]-360
461      toosmall = where(glamu EQ glamboundary[0])
462      IF toosmall[0] NE -1 THEN glamu[toosmall] = glamu[toosmall] + 360
463      toosmall = where(glamf EQ glamboundary[0])
464      IF toosmall[0] NE -1 THEN glamf[toosmall] = glamf[toosmall] + 360
465    endif
466  endif
467;-------------------------------------------------------
468; make sure we do have 2d arrays when jpj eq 1
469;-------------------------------------------------------
470  IF jpj EQ 1 THEN BEGIN
471    glamt = reform(glamt, jpi, jpj, /over)
472    gphit = reform(gphit, jpi, jpj, /over)
473    e1t = reform(e1t, jpi, jpj, /over)
474    e2t = reform(e2t, jpi, jpj, /over)
475    glamu = reform(glamu, jpi, jpj, /over)
476    gphiu = reform(gphiu, jpi, jpj, /over)
477    e1u = reform(e1u, jpi, jpj, /over)
478    e2u = reform(e2u, jpi, jpj, /over)
479    glamv = reform(glamv, jpi, jpj, /over)
480    gphiv = reform(gphiv, jpi, jpj, /over)
481    e1v = reform(e1v, jpi, jpj, /over)
482    e2v = reform(e2v, jpi, jpj, /over)
483    glamf = reform(glamf, jpi, jpj, /over)
484    gphif = reform(gphif, jpi, jpj, /over)
485    e1f = reform(e1f, jpi, jpj, /over)
486    e2f = reform(e2f, jpi, jpj, /over)
487  ENDIF
488;-------------------------------------------------------
489  ixmindta = ixmindtasauve
490  iymindta = iymindtasauve
491  izmindta = izmindtasauve
492;-------------------------------------------------------
493  widget_control, noticebase, bad_id = nothing, /destroy
494;
495;====================================================
496; grid parameters used by xxx
497;====================================================
498;
499  IF NOT keyword_set(strcalling) THEN BEGIN
500    IF n_elements(ccmeshparameters) EQ 0 THEN strcalling = 'ncdf_meshroms' $
501    ELSE strcalling = ccmeshparameters.filename
502  ENDIF
503  IF n_elements(glamt) GE 2 THEN BEGIN
504    glaminfo = moment(glamt)
505    IF finite(glaminfo[2]) EQ 0 THEN glaminfo = glaminfo[0:1]
506    gphiinfo = moment(gphit)
507    IF finite(gphiinfo[2]) EQ 0 THEN gphiinfo = gphiinfo[0:1]
508  ENDIF ELSE BEGIN
509    glaminfo = glamt
510    gphiinfo = gphit
511  ENDELSE
512  romszinfos = {h:hroms, zeta:replicate(0., jpi, jpj), theta_s:-1, theta_b:-1, hc:-1}
513  ccmeshparameters = {filename:strcalling  $
514          , glaminfo:float(string(glaminfo, format = '(E11.4)')) $
515          , gphiinfo:float(string(gphiinfo, format = '(E11.4)')) $
516          , jpiglo:jpiglo, jpjglo:jpjglo, jpkglo:jpkglo $
517          , jpi:jpi, jpj:jpj, jpk:jpk $
518          , ixminmesh:ixminmesh, ixmaxmesh:ixmaxmesh $
519          , iyminmesh:iyminmesh, iymaxmesh:iymaxmesh $
520          , izminmesh:izminmesh, izmaxmesh:izmaxmesh $
521          , key_shift:key_shift, key_periodic:key_periodic $
522          , key_stride:key_stride, key_gridtype:key_gridtype $
523          , key_yreverse:key_yreverse, key_zreverse:key_zreverse $
524          , key_partialstep:key_partialstep, key_onearth:key_onearth}
525;
526  if keyword_set(key_performance) THEN $
527    print, 'time ncdf_meshread', systime(1)-tempsun
528
529;-------------------------------------------------------
530   @updateold
531;-------------------------------------------------------
532   return
533 end
Note: See TracBrowser for help on using the repository browser.