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

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

bugfix ncdf_meshread + comments in compute_fromreg_bilinear_weigaddr

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