source: trunk/SRC/Grid/computegrid.pro @ 76

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

debug xxx and cie + clean data file + rm perldoc_idl

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 40.6 KB
Line 
1;------------------------------------------------------------
2;------------------------------------------------------------
3;------------------------------------------------------------
4;+
5; NAME:computegrid
6;
7; PURPOSE:compute the grid parameters from cm_4mesh common:
8;
9; horizontal parameters:
10;       glam[tf], gphi[tf], e1t and e2t
11;    and if FULLCGRID keyword is defined:
12;       glam[uv], gphi[uv], e1[uvf] and e2[uvf]
13;     
14; verticals parameters:
15;       gdep[tw], e3[tw]
16;
17; masks: tmask
18;        and if FULLCGRID keyword is defined:[uv]maskred fmaskred[xy]
19;
20; triangulation: triangles_list
21;
22; key_ parameters:
23;       key_shift, key_periodic, key_zreverse, key_yreverse,
24;       key_stride, key_onearth, key_partialstep
25;
26; CATEGORY:grid
27;
28; CALLING SEQUENCE:
29;
30;       computegrid, startx, starty, stepx, stepy, nx, ny
31;       computegrid, startx, starty, stepx, stepy
32;       computegrid, xaxis = xaxis, yaxis = yaxis
33;       or a suitable mix...
34;
35; INPUTS:
36;       startx:scalar, x starting point
37;       starty:scalar, y starting point
38;       stepx:scalar or vector: x direction step, must be > 0
39;             if vector nx is not used
40;       stepy:scalar or vector: y direction step,
41;             could be > 0 (south to north) or < 0 (north to south)
42;             if vector ny is not used
43;       nx:scalar, number of points in x direction
44;       ny:scalar, number of points in y direction
45;
46; KEYWORD PARAMETERS:
47;
48;       /FULLCGRID: activate to specify that you want to compute
49;       all the paremeters of a C grid. Computation of glam[uv],
50;       gphi[uv], e1[uvf], e2[uvf], [uv]maskred and fmaskred[xy]
51;       will be add to the default computations
52;
53;       GLAMBOUNDARY: a 2 elements vector, [lon1,lon2], the longitute
54;       boundaries that should be used to visualize the data.
55;       we must have lon2 > lon1 and lon2 - lon1 le 360
56;       key_shift will be defined automaticaly computed according to
57;       glamboundary by using the FIRST LINE of glamt but
58;       key_shift will /= 0 only if key_periodic = 1
59;
60;       MASK: to specify the mask with a 2 or 3 dimension array
61;
62;       ONEARTH = 0 or 1: to force the manual definition of
63;       key_onearth (to specify if the data are on earth -> use longitude
64;       /latitude etc...). By default, key_onearth = 1.
65;       note that ONEARTH = 0 forces PERIODIC = 0, SHIFT = 0,
66;       and is cancelling GLAMBOUNDARY
67;
68;       PERIODIC = 0 or 1: to force the manual definition of
69;       key_periodic. By default, key_periodic is automaticaly
70;       computed by using the first line of glamt.
71;
72;       /PLAIN: force PERIODIC = 0, SHIFT = 0, STRIDE = [1, 1, 1] and
73;       suppress the automatic redefinition of the domain in case of
74;       x periodicity overlap, y periodicity overlap (ORCA type only)
75;       and mask border to 0.
76;
77;       SHIFT = scalar to force the manual definition of key_shift. By
78;       debault, key_shift is automaticaly computed according to
79;       glamboundary (when defined) by using the FIRST LINE of glamt. if
80;       key_periodic=0 then in any case key_shift = 0.
81;
82;       STRCALLING: a string containing the calling command used to
83;       call computegrid (this is used by xxx.pro)
84;
85;       STRIDE = : a 3 elements vector to specify the stride in x, y, z
86;       direction. Default definition is [1, 1, 1]. The resulting value
87;       will be stored in the common (cm_4mesh) variable key_stride
88;
89;       XAXIS: to specify longitude1 with a 1 or 2 dimension array, in
90;       this case startx, stepx and nx are not used but could be
91;       necessary if the y axis is not defined with yaxis. It must be
92;       possible to sort the first line of xaxis in the increasing
93;       order by shifting its elements.
94;
95;       YAXIS: to specify latitudes with a 1 or 2 dimension array, in
96;       this case starty, stepy and ny are not used but starty and
97;       stepy could be necessary if the x axis is not defined with xaxis.
98;       It must be sorted in the increasing or deceasing order
99;       (along each column if 2d array).
100;
101;       /XYINDEX: activate to specify that the horizontal grid should
102;       be simply defined by using the index of the points
103;          (xaxis = findgen(nx) and yaxis = findgen(ny))
104;       using this keyword forces key_onearth=0
105;
106;       [XYZ]MINMESH: to define the common variables i[xyz]minmesh
107;       used to define the grid only in a zoomed part of the original
108;       grid. Defaut values are 0L, max value is [XYZ]MAXMESH
109;
110;       [XYZ]MAXMESH: to define the common variables i[xyz]maxmesh
111;       used to define the grid only in a zoomed part of the original
112;       grid. Defaut values are jp[ijk]glo-1, max value is
113;       jp[ijk]glo-1. if [XYZ]MAXMESH is negative, then we define
114;       i[xyz]maxmesh as jp[ijk]glo - 1 + [XYZ]MAXMESH instead of
115;       [XYZ]MAXMESH   
116;
117;       ZAXIS: to specify the vertical axis with a 1 dimension
118;       array. Must be sorted in the increasing or deceasing order
119;
120; OUTPUTS:
121;
122; COMMON BLOCKS: cm_4mesh cm_4data cm_4cal
123;
124; SIDE EFFECTS: if the grid has x/y periodicity orverlap and/or if
125;    the mask has 0 everywhere at the border (like a close sea) and
126;    if (we did not activate /plain and xminmesh, xmaxmesh, yminmesh,
127;    ymaxmesh keywords are defined to their default values), we redefine
128;    xminmesh, xmaxmesh, yminmesh, ymaxmesh in order to reove the
129;    overlapping part and/or to open the domain (avoid ti be forced
130;    to use cell_fill = 1).
131;
132; RESTRICTIONS:FUV points definition...
133;
134; EXAMPLE:
135;
136; MODIFICATION HISTORY:Sebastien Masson (smasson@lodyc.jussieu.fr)
137;                      2000-04-20
138;  Sept 2004, several bug fixs to suit C grid type...
139;  Aug 2005, rewritte almost everything...
140;-
141;------------------------------------------------------------
142;------------------------------------------------------------
143;------------------------------------------------------------
144PRO computegrid, startx, starty, stepxin, stepyin, nxin, nyin $
145                 , XAXIS = xaxis, YAXIS = yaxis, ZAXIS = zaxis $
146                 , MASK = mask, GLAMBOUNDARY = glamboundary $
147                 , XMINMESH = xminmesh, XMAXMESH = xmaxmesh $
148                 , YMINMESH = yminmesh, YMAXMESH = ymaxmesh $
149                 , ZMINMESH = zminmesh, ZMAXMESH = zmaxmesh $
150                 , ONEARTH = onearth, PERIODIC = periodic $
151                 , PLAIN = plain, SHIFT = shift, STRIDE = stride $
152                 , FULLCGRID = fullcgrid, XYINDEX = xyindex $
153                 , FBASE2TBASE = fbase2tbase, STRCALLING = strcalling $
154                 , _extra = ex
155;---------------------------------------------------------
156@cm_4mesh
157@cm_4data
158@cm_4cal
159  IF NOT keyword_set(key_forgetold) THEN BEGIN
160@updatenew
161@updatekwd
162  ENDIF
163;---------------------------------------------------------
164;------------------------------------------------------------
165  time1 = systime(1)            ; for key_performance
166;------------------------------------------------------------
167;
168;====================================================
169; Check input parameters
170;====================================================
171;
172; xaxis related parameters
173;
174  if n_elements(xaxis) NE 0 then BEGIN
175    CASE (size(xaxis))[0] OF
176      0:nx = 1L
177      1:nx = (size(xaxis))[1]
178      2:nx = (size(xaxis))[1]
179    ENDCASE
180  ENDIF ELSE BEGIN
181    IF n_elements(startx) EQ 0 THEN BEGIN
182      dummy = report('If xaxis is not given, startx must be defined')
183      return
184    ENDIF
185    CASE n_elements(stepxin) OF
186      0:BEGIN
187        dummy = report('If xaxis is not given, stepxin must be defined')
188        return
189      END
190      1:BEGIN
191        IF n_elements(nxin) EQ 0 THEN BEGIN
192          dummy = report('If xaxis is not given and stepxin has only one element, nx must be defined')
193          return
194        ENDIF ELSE nx = nxin
195      END
196      ELSE:nx = n_elements(stepxin)   
197    ENDCASE
198  ENDELSE
199;
200; yaxis related parameters
201;
202  if n_elements(yaxis) NE 0 then BEGIN
203    CASE (size(yaxis))[0] OF
204      0:ny = 1L
205      1:ny = (size(yaxis))[1]
206      2:ny = (size(yaxis))[2]
207    ENDCASE
208  ENDIF ELSE BEGIN
209    IF n_elements(starty) EQ 0 THEN BEGIN
210      dummy = report('If yaxis is not given, starty must be defined')
211      return
212    ENDIF
213    CASE n_elements(stepyin) OF
214      0:BEGIN
215        dummy = report('If yaxis is not given, stepyin must be defined')
216        return
217      END
218      1:BEGIN
219        IF n_elements(nyin) EQ 0 THEN BEGIN
220          dummy = report('If yaxis is not given and stepyin has only one element, ny must be defined')
221          return
222        ENDIF ELSE ny = nyin
223      END
224      ELSE:ny = n_elements(stepyin)   
225    ENDCASE
226  ENDELSE
227;
228; zaxis related parameters
229;
230  if n_elements(zaxis) NE 0 then BEGIN
231    CASE (size(zaxis))[0] OF
232      0:nz = 1L
233      1:nz = (size(zaxis))[1]
234      ELSE:BEGIN
235        print, 'not coded'
236        stop
237      END
238    ENDCASE
239  ENDIF ELSE nz = 1L
240;
241;====================================================
242; Others automatic definitions...
243;====================================================
244;
245  jpiglo = long(nx)
246  jpjglo = long(ny)
247  jpkglo = long(nz)
248;
249; impact of plain keyword:
250;
251  IF keyword_set(plain) THEN BEGIN
252    periodic = 0
253    shift = 0
254    stride = [1, 1, 1]
255  ENDIF
256;
257  IF n_elements(xminmesh) NE 0 THEN ixminmesh = long(xminmesh[0]) ELSE ixminmesh  = 0l
258  IF n_elements(xmaxmesh) NE 0 THEN ixmaxmesh = long(xmaxmesh[0]) ELSE ixmaxmesh  = jpiglo-1
259  IF n_elements(yminmesh) NE 0 THEN iyminmesh = long(yminmesh[0]) ELSE iyminmesh  = 0l
260  IF n_elements(ymaxmesh) NE 0 THEN iymaxmesh = long(ymaxmesh[0]) ELSE iymaxmesh  = jpjglo-1
261  IF n_elements(zminmesh) NE 0 THEN izminmesh = long(zminmesh[0]) ELSE izminmesh  = 0l
262  IF n_elements(zmaxmesh) NE 0 THEN izmaxmesh = long(zmaxmesh[0]) ELSE izmaxmesh  = jpkglo-1
263;
264  iymaxmesh = iymaxmesh-keyword_set(fbase2tbase)
265;
266  IF ixmaxmesh LT 0 THEN ixmaxmesh = jpiglo -1 + ixmaxmesh
267  IF iymaxmesh LT 0 THEN iymaxmesh = jpjglo -1 + iymaxmesh
268  IF izmaxmesh LT 0 THEN izmaxmesh = jpkglo -1 + izmaxmesh
269; avoid basics errors...
270  ixmaxmesh = 0 > ixmaxmesh < (jpiglo-1)
271  ixminmesh = 0 > ixminmesh < ixmaxmesh
272  iymaxmesh = 0 > iymaxmesh < (jpjglo-1)
273  iyminmesh = 0 > iyminmesh < iymaxmesh
274  izmaxmesh = 0 > izmaxmesh < (jpkglo-1)
275  izminmesh = 0 > izminmesh < izmaxmesh
276;
277  jpi = ixmaxmesh-ixminmesh+1
278  jpj = iymaxmesh-iyminmesh+1
279  jpk = izmaxmesh-izminmesh+1
280;
281  jpidta = jpiglo
282  jpjdta = jpjglo
283  jpkdta = jpkglo
284  ixmindta = 0
285  ixmaxdta = jpidta-1
286  iymindta = 0
287  iymaxdta = jpjdta-1
288  izmindta = 0
289  izmaxdta = jpkdta-1
290;
291  key_partialstep = 0
292  if n_elements(stride) eq 3 then key_stride = stride $
293  ELSE key_stride = [1, 1, 1]
294  key_gridtype = 'c'
295;
296; check xyindex and its consequences
297;
298  if keyword_set(xyindex) then onearth = 0
299;
300; check onearth and its consequences
301;
302  IF n_elements(onearth) EQ 0 THEN key_onearth = 1b $
303  ELSE key_onearth = keyword_set(onearth)
304  IF NOT key_onearth THEN BEGIN
305    periodic = 0
306    shift = 0
307  ENDIF
308
309  r = 6371000.
310;
311;====================================================
312; X direction : glamt
313;====================================================
314;
315; def of glamt
316;
317  if n_elements(xaxis) NE 0 then BEGIN
318    if keyword_set(xyindex) THEN glamt = findgen(jpiglo) ELSE glamt = xaxis
319  ENDIF ELSE BEGIN
320    if keyword_set(xyindex) THEN stepx = 1. ELSE stepx = stepxin
321    CASE 1 OF
322      n_elements(stepx):glamt = startx + findgen(jpiglo)*stepx
323      size(stepx, /n_dimensions):glamt = startx + total(stepx, /cumulative)
324      ELSE:BEGIN
325        dummy = report('Wrong definition of stepx...')
326        return
327      END
328    ENDCASE
329  ENDELSE
330;
331; apply glamboundary
332;
333  IF keyword_set(glamboundary) AND key_onearth THEN BEGIN
334    IF glamboundary[0] GE glamboundary[1] THEN stop
335    IF glamboundary[1]-glamboundary[0] GT 360 THEN stop
336    glamt = glamt MOD 360
337    smaller = where(glamt LT glamboundary[0])
338    if smaller[0] NE -1 then glamt[smaller] = glamt[smaller]+360.
339    bigger = where(glamt GE glamboundary[1])
340    if bigger[0] NE -1 then glamt[bigger] = glamt[bigger]-360.
341  ENDIF
342;
343; force glamt to have 2 dimensions
344;
345  CASE size(reform(glamt), /n_dimensions) OF
346    0:glamt = replicate(glamt, jpi, jpj)
347    1:glamt = glamt[ixminmesh:ixmaxmesh]#replicate(1, jpj)
348    2:glamt = glamt[ixminmesh:ixmaxmesh, iyminmesh:iymaxmesh]
349  ENDCASE
350; keep 2d array even with degenereted dimension
351  IF jpj EQ 1 THEN glamt = reform(glamt, jpi, jpj, /over)
352;
353;====================================================
354; Y direction : gphit
355;====================================================
356;
357; def of gphit
358;
359  if n_elements(yaxis) NE 0 THEN BEGIN
360    if keyword_set(xyindex) THEN gphit = findgen(jpjglo) ELSE gphit = yaxis
361  ENDIF ELSE BEGIN
362    if keyword_set(xyindex) THEN stepy = 1. ELSE stepy = stepyin
363    CASE 1 OF
364      n_elements(stepy):gphit = starty + findgen(jpjglo)*stepy
365      size(stepy, /n_dimensions):gphit = starty + total(stepy, /cumulative)
366      ELSE:BEGIN
367        dummy = report('Wrong definition of stepy...')
368        return
369      END
370    ENDCASE
371  ENDELSE
372;
373; force gphit to have 2 dimensions
374;
375  CASE size(reform(gphit), /n_dimensions) OF
376    0:gphit = replicate(gphit, jpi, jpj)
377    1:gphit = replicate(1, jpi)#gphit[iyminmesh:iymaxmesh]
378    2:gphit = gphit[ixminmesh:ixmaxmesh, iyminmesh:iymaxmesh]
379  ENDCASE
380; keep 2d array even with degenereted dimension
381  IF jpj EQ 1 THEN gphit = reform(gphit, jpi, jpj, /over)
382;
383;====================================================
384; check y periodicity... Only according to ORCA grid
385;====================================================
386; check the peridicity if iyminmesh and iymaxmesh have the default definitions...
387  IF NOT keyword_set(plain) AND key_onearth EQ 1 AND key_stride[1] EQ 1 $
388    AND iyminmesh EQ 0l AND iymaxmesh eq jpjglo-1 AND jpj GE 3 AND jpi GE 2 THEN BEGIN
389
390    CASE 1 OF
391      ixminmesh EQ 0l AND ixmaxmesh eq jpiglo-1 $
392        AND array_equal(gphit[1:*, jpj-1], reverse(gphit[1:*, jpj-3])) EQ 1:BEGIN
393; T pivot
394        ymaxmesh = -1
395        recall = 1
396      END
397      ixminmesh EQ 1l AND ixmaxmesh eq jpiglo-2 $
398         AND array_equal(gphit[*, jpj-1], reverse(shift(gphit[*, jpj-3], -1))) EQ 1:BEGIN
399; T pivot
400        ymaxmesh = -1
401        recall = 1
402      END
403      ixminmesh EQ 0l AND ixmaxmesh eq jpiglo-1 $
404       AND array_equal(gphit[*, jpj-1], reverse(gphit[*, jpj-2])) EQ 1:BEGIN
405; F pivot
406        ymaxmesh = -1
407        recall = 1
408      END
409      ixminmesh EQ 1l AND ixmaxmesh eq jpiglo-2 $
410         AND array_equal(gphit[*, jpj-1], reverse(gphit[*, jpj-2])) EQ 1:BEGIN
411; F pivot
412        ymaxmesh = -1
413        recall = 1
414      END
415      ELSE:
416    ENDCASE
417  ENDIF
418;
419;====================================================
420; check x periodicity...
421;====================================================
422IF n_elements(periodic) NE 0 THEN forcenoperio = 1 - keyword_set(periodic)
423;                                                    check the peridicity if ixminmesh and ixmaxmesh have the default definitions...
424  IF NOT keyword_set(plain) AND NOT keyword_set(forcenoperio) AND key_onearth EQ 1 $
425     AND key_stride[0] EQ 1 AND ixminmesh EQ 0l AND ixmaxmesh eq jpiglo-1 AND jpi GE 3 THEN BEGIN
426    CASE 0 OF
427      total((glamt[0, *] - glamt[jpi-2, *]) MOD 360) $
428      + total((glamt[1, *] - glamt[jpi-1, *]) MOD 360):BEGIN
429        xminmesh = 1
430        xmaxmesh = -1
431        recall = 1
432      END
433      total((glamt[0, *] - glamt[jpi-2, *]) MOD 360):BEGIN
434        xminmesh = 1
435        recall = 1
436      END
437      total((glamt[1, *] - glamt[jpi-1, *]) MOD 360):BEGIN
438        xmaxmesh = -1
439        recall = 1
440      END
441      ELSE:
442    ENDCASE
443  ENDIF
444;====================================================
445; recall computegrid if needed...
446;====================================================
447  IF keyword_set(recall) THEN BEGIN
448    computegrid, XAXIS = glamt, YAXIS = gphit, ZAXIS = zaxis $
449                 , MASK = mask, GLAMBOUNDARY = glamboundary $
450                 , XMINMESH = xminmesh, XMAXMESH = xmaxmesh $
451                 , YMINMESH = yminmesh, YMAXMESH = ymaxmesh $
452                 , ZMINMESH = zminmesh, ZMAXMESH = zmaxmesh $
453                 , PERIODIC = periodic, SHIFT = shift, STRIDE = stride $
454                 , FULLCGRID = fullcgrid, XYINDEX = xyindex $
455                 , FBASE2TBASE = fbase2tbase, STRCALLING = strcalling $
456                 , _extra = ex
457    return
458  ENDIF
459;====================================================
460; def of key_shift
461;====================================================
462;
463; definition of key_shift by shiftting the array to have the min
464; values of glamt[*, 0] in glamt[0, 0]
465;
466  IF n_elements(shift) EQ 0 THEN BEGIN
467    IF jpi GT 1 then BEGIN
468      xtest = glamt[*, 0]
469      key_shift = (where(xtest EQ min(xtest)))[0]
470      IF key_shift NE 0 THEN key_shift = jpi - key_shift
471    ENDIF ELSE key_shift = 0
472  ENDIF ELSE key_shift = shift
473;
474;====================================================
475; def of key_periodic
476;====================================================
477;
478  IF n_elements(periodic) EQ 0 THEN BEGIN
479    IF jpi GT 1 THEN BEGIN
480      xtest = shift(glamt[*, 0], key_shift)
481; check that xtest is now sorted in the increasing order
482      IF array_equal(sort(xtest), lindgen(jpi)) EQ 0 THEN BEGIN
483        print, 'WARNING: we cannot sort the xaxis with a simple shift...'
484        print, 'we force key_periodic = 0 and key_shift = 0'
485        print, 'only horizontal plot may be ok...'
486        key_periodic = 0
487        xnotsorted = 1
488      ENDIF ELSE BEGIN
489        key_periodic = (xtest[jpi-1]+2*(xtest[jpi-1]-xtest[jpi-2])) $
490                       GE (xtest[0]+360)
491      ENDELSE
492    ENDIF ELSE key_periodic = 0
493  ENDIF ELSE key_periodic = keyword_set(periodic)
494;
495; update key_shift
496;
497  key_shift = key_shift * (key_periodic EQ 1)
498;
499  IF NOT keyword_set(key_periodic) AND keyword_set(fbase2tbase) THEN BEGIN
500    ixmaxmesh = ixmaxmesh-1
501    jpi = jpi-1
502  ENDIF
503;
504;====================================================
505; apply key_shift
506;====================================================
507;
508  if keyword_set(key_shift) then BEGIN
509    glamt = shift(glamt, key_shift, 0)
510    gphit = shift(gphit, key_shift, 0)
511    IF jpj EQ 1 THEN BEGIN
512      glamt = reform(glamt, jpi, jpj, /over)
513      gphit = reform(gphit, jpi, jpj, /over)
514    ENDIF
515  ENDIF
516;
517;====================================================
518; def key_yreverse
519;====================================================
520;
521  IF jpj GT 1 THEN BEGIN
522    if gphit[0, 1] LT gphit[0, 0] then begin
523      key_yreverse = 1
524      gphit = reverse(gphit, 2)
525      glamt = reverse(glamt, 2)
526    ENDIF ELSE key_yreverse = 0
527  ENDIF ELSE key_yreverse = 0
528;
529;====================================================
530; Are we using a "regular" grid (that can be described
531; with x vector and y vector)?
532;====================================================
533;
534; to get faster, we first test the most basic cases before
535; testing the full array.
536;
537  CASE 1 OF
538    keyword_set(xyindex):key_irregular = 0b
539    jpi EQ 1 OR jpj EQ 1:key_irregular = 0b
540    n_elements(xaxis) EQ 0 AND n_elements(yaxis) EQ 0:key_irregular = 0b
541    size(reform(xaxis), /n_dimensions) EQ 1 AND size(reform(xaxis), /n_dimensions) EQ 1:key_irregular = 0b
542    n_elements(xaxis) EQ 0 AND size(reform(yaxis), /n_dimensions) EQ 1:key_irregular = 0b
543    n_elements(yaxis) EQ 0 AND size(reform(xaxis), /n_dimensions) EQ 1:key_irregular = 0b
544    array_equal(glamt[*, 0], glamt[*, jpj-1]) EQ 0:key_irregular = 1b
545    array_equal(gphit[0, *], gphit[jpi-1, *]) EQ 0:key_irregular = 1b
546    array_equal(glamt, glamt[*, 0]#replicate(1, jpj)) EQ 0:key_irregular = 1b
547    array_equal(gphit, replicate(1, jpi)#(gphit[0, *])[*]) EQ 0:key_irregular = 1b
548    ELSE:key_irregular = 0b
549  ENDCASE
550;
551;====================================================
552; def of glamf: defined as the middle of T(i,j) T(i+1,j+1)
553;====================================================
554;
555  IF jpi GT 1 THEN BEGIN
556; we must compute stepxf: x distance between T(i,j) T(i+1,j+1)
557    CASE 1 OF
558      n_elements(stepx):stepxf = stepx
559      size(stepx, /n_dimensions):stepxf = stepx#replicate(1, jpj)
560      ELSE:BEGIN
561        if (keyword_set(key_onearth) AND keyword_set(xnotsorted)) $
562          OR (keyword_set(key_periodic) AND key_irregular) then BEGIN
563          stepxf = (glamt + 720) MOD 360
564          IF jpj EQ 1 THEN stepxf = reform(stepxf, jpi, jpj, /over)
565          stepxf = shift(stepxf, -1, -1) - stepxf
566          stepxf = [ [[stepxf]], [[stepxf + 360]], [[stepxf - 360]] ]
567          stepxf = min(abs(stepxf), dimension = 3)
568          IF NOT keyword_set(key_periodic) THEN $
569            stepxf[jpi-1, *] = stepxf[jpi-2, *]
570        ENDIF ELSE BEGIN
571          stepxf = shift(glamt, -1, -1) - glamt
572          IF keyword_set(key_periodic) THEN $
573            stepxf[jpi-1, *] = 360 + stepxf[jpi-1, *] $
574          ELSE stepxf[jpi-1, *] = stepxf[jpi-2, *]
575        ENDELSE
576        IF jpj GT 1 THEN BEGIN
577          stepxf[*, jpj-1] = stepxf[*, jpj-2]
578          stepxf[jpi-1, jpj-1] = stepxf[jpi-2, jpj-2]
579        ENDIF
580      END
581    ENDCASE
582    glamf = glamt + 0.5 * stepxf
583  ENDIF ELSE glamf = glamt + 0.5
584;
585  IF keyword_set(key_periodic) AND (max(glamf)-min(glamt)) GE 360 THEN BEGIN
586    IF NOT keyword_set(glamboundary) THEN BEGIN
587      bigger = where(glamf GE min(glamt)+360)
588      glamf[bigger] = glamf[bigger]-360.
589    ENDIF ELSE glamf = glamboundary[0] > temporary(glamf) < glamboundary[1]
590  ENDIF
591;
592  IF jpj EQ 1 THEN glamf = reform(glamf, jpi, jpj, /over)
593;
594;====================================================
595; def of gphif: defined as the middle of T(i,j) T(i+1,j+1)
596;====================================================
597;
598  IF jpj GT 1 THEN BEGIN
599; we must compute stepyf: y distance between T(i,j) T(i+1,j+1)
600    CASE 1 OF
601      n_elements(stepy):stepyf = stepy
602      size(stepy, /n_dimensions):stepyf = replicate(1, jpi)#stepy
603      ELSE:BEGIN
604        stepyf = shift(gphit, -1, -1) - gphit
605        stepyf[*, jpj-1] = stepyf[*, jpj-2]
606        IF jpi GT 1 THEN BEGIN
607          if NOT keyword_set(key_periodic) THEN $
608            stepyf[jpi-1, *] = stepyf[jpi-2, *]
609          stepyf[jpi-1, jpj-1] = stepyf[jpi-2, jpj-2]
610        ENDIF
611      END
612    ENDCASE
613    gphif = gphit + 0.5 * stepyf
614  ENDIF ELSE gphif = gphit + 0.5
615  IF key_onearth THEN gphif = -90. > gphif < 90.
616;
617  IF jpj EQ 1 THEN gphif = reform(gphif, jpi, jpj, /over)
618;
619;====================================================
620; e1t: x distance between U(i-1,j) and U(i,j)
621;====================================================
622;
623; *-|-*---|---*---|
624;
625  IF jpi GT 1 THEN BEGIN
626    IF n_elements(stepx) NE 1 THEN BEGIN
627      IF keyword_set(irregular) THEN BEGIN
628; we must compute stepxu: x distance between T(i,j) T(i+1,j)
629        IF keyword_set(key_periodic) THEN BEGIN
630          stepxu = (glamt + 720) MOD 360
631          stepxu = shift(stepxu, -1, 0) - stepxu
632          stepxu = [ [[stepxu]], [[stepxu + 360]], [[stepxu - 360]] ]
633          stepxu = min(abs(stepxu), dimension = 3)
634        ENDIF ELSE BEGIN
635          stepxu = shift(glamt, -1, 0) - glamt
636          stepxu[jpi-1, *] = stepxf[jpi-2, *]
637        ENDELSE
638      ENDIF ELSE stepxu = stepxf
639      IF jpj EQ 1 THEN stepxu = reform(stepxu, jpi, jpj, /over)
640      e1t = 0.5*(stepxu+shift(stepxu, 1, 0))
641      IF NOT keyword_set(key_periodic) THEN $
642        e1t[0, *] = e1t[1, *]
643    ENDIF ELSE e1t = replicate(stepx, jpi, jpj)
644  ENDIF ELSE e1t = replicate(1b, jpi, jpj)
645;
646  IF jpj EQ 1 THEN e1t = reform(e1t, jpi, jpj, /over)
647;
648;====================================================
649; e2t: y distance between V(i,j-1) and V(i,j)
650;====================================================
651;
652  IF jpj GT 1 THEN BEGIN
653; we must compute stepyv: y distance between T(i,j) T(i,j+1)
654    IF n_elements(stepy) NE 1 THEN BEGIN
655      IF keyword_set(key_irregular) THEN BEGIN
656        stepyv = shift(gphit, 0, -1) - gphit
657        stepyv[*, jpj-1] = stepyv[*, jpj-2]
658      ENDIF ELSE stepyv = stepyf
659      e2t = 0.5*(stepyv+shift(stepyv, 0, 1))
660      e2t[*, 0] = e2t[*, 1]
661    ENDIF ELSE e2t = replicate(stepy, jpi, jpj)
662  ENDIF ELSE e2t = replicate(1b, jpi, jpj)
663;
664  IF key_onearth THEN e2t = r * !pi/180. * temporary(e2t)
665;
666  IF jpj EQ 1 THEN e2t = reform(e2t, jpi, jpj, /over)
667;
668;~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
669  IF keyword_set(fullcgrid) THEN BEGIN
670;
671;====================================================
672; def of glamu: defined as the middle of T(i,j) T(i+1,j)
673;====================================================
674;
675    IF keyword_set(irregular) THEN BEGIN
676      glamu = glamt + 0.5 * stepxu
677      IF keyword_set(glamboundary) AND key_onearth THEN $
678        glamu = glamboundary[0] > temporary(glamu) < glamboundary[1]
679    ENDIF ELSE glamu = glamf
680;
681    IF jpj EQ 1 THEN glamu = reform(glamu, jpi, jpj, /over)
682;
683;====================================================
684; def of gphiu: defined as the middle of T(i,j) T(i+1,j)
685;====================================================
686;
687    IF jpi GT 1 THEN BEGIN
688 ; we must compute stepyu: y distance between T(i+1,j) T(i,j)
689      IF keyword_set(key_irregular) THEN BEGIN
690       stepyu = shift(gphit, -1, 0) - gphit
691        IF NOT keyword_set(key_periodic) THEN $
692          stepyu[jpi-1, *] = stepyu[jpi-2, *]
693        gphiu = gphit + 0.5 * stepyu
694      ENDIF ELSE gphiu = gphit
695    ENDIF ELSE gphiu = gphit
696  IF key_onearth THEN gphiu = -90. > gphiu < 90.
697;
698  IF jpj EQ 1 THEN gphiu = reform(gphiu, jpi, jpj, /over)
699;
700;====================================================
701; def of glamv: defined as the middle of T(i,j) T(i,j+1)
702;====================================================
703;
704    IF jpj GT 1 THEN BEGIN
705 ; we must compute stepxv: x distance between T(i,j) T(i,j+1)
706      IF keyword_set(irregular) THEN BEGIN
707        IF keyword_set(key_periodic) THEN BEGIN
708          stepxv = (glamt + 720) MOD 360
709          stepxv = shift(stepxv, 0, -1) - stepxv
710          stepxv = [ [[stepxv]], [[stepxv + 360]], [[stepxv - 360]] ]
711          stepxv = min(abs(stepxv), dimension = 3)
712        ENDIF ELSE stepxv = shift(glamt, 0, -1) - glamt
713        stepxv[*, jpj-1] = stepxv[*, jpj-2]
714        glamv = glamt + 0.5 * stepxv
715        IF keyword_set(glamboundary) AND key_onearth THEN $
716          glamv = glamboundary[0] > temporary(glamv) < glamboundary[1]
717      ENDIF ELSE glamv = glamt
718    ENDIF ELSE glamv = glamt
719;
720;====================================================
721; def of gphiv: defined as the middle of T(i,j) T(i,j+1)
722;====================================================
723;
724    IF keyword_set(key_irregular) THEN $       
725      gphiv = gphit + 0.5 * stepyv $
726    ELSE gphiv = gphif
727    IF key_onearth THEN gphiv = -90. > gphiv < 90.
728;
729    IF jpj EQ 1 THEN gphiv = reform(gphiv, jpi, jpj, /over)
730;
731;====================================================
732; e1u: x distance between T(i,j) and T(i+1,j)
733;====================================================
734;
735    IF jpi GT 1 AND n_elements(stepx) NE 1 THEN $
736      e1u = stepxu ELSE e1u = e1t
737;
738;====================================================
739; e2u: y distance between F(i,j-1) and F(i,j)
740;====================================================
741;
742    IF keyword_set(key_irregular) THEN BEGIN
743      e2u = gphif - shift(gphif, 0, 1)
744      e2u[*, 0] = e2u[*, 1]
745      IF key_onearth THEN e2u = r * !pi/180. * temporary(e2u)
746    ENDIF ELSE e2u = e2t
747;
748    IF jpj EQ 1 THEN e2u = reform(e2u, jpi, jpj, /over)
749;
750;====================================================
751; e1v: x distance between F(i-1,j) and F(i,j)
752;====================================================
753;
754    IF keyword_set(irregular) THEN BEGIN
755      IF keyword_set(key_periodic) THEN BEGIN
756        e1v = (glamf + 720) MOD 360
757        e1v = e1v - shift(e1v, 1, 0)
758        e1v = [ [[e1v]], [[e1v + 360]], [[e1v - 360]] ]
759        e1v = min(abs(e1v), dimension = 3)
760      ENDIF ELSE BEGIN
761        e1v = glamf - shift(glamf, 1, 0)
762        e1v[0, *] = stepxf[1, *]
763      ENDELSE
764    ENDIF ELSE e1v = e1t
765;
766    IF jpj EQ 1 THEN e1v = reform(e1v, jpi, jpj, /over)
767;
768;====================================================
769; e2v: y distance between T(i,j) and T(i+1,j)
770;====================================================
771;
772    IF jpj GT 1 and n_elements(stepy) NE 1 THEN BEGIN
773      e2v = stepyv
774      IF key_onearth THEN e2v = r * !pi/180. * temporary(e2v)
775    ENDIF ELSE e2v = e2t
776;
777;====================================================
778; e1f: x distance between V(i,j) and V(i+1,j)
779;====================================================
780;
781    IF keyword_set(irregular) THEN BEGIN
782      IF keyword_set(key_periodic) THEN BEGIN
783        e1f = (glamv + 720) MOD 360
784        e1f = shift(e1f, -1, 0) - e1f
785        e1f = [ [[e1f]], [[e1f + 360]], [[e1f - 360]] ]
786        e1f = min(abs(e1f), dimension = 3)
787      ENDIF ELSE BEGIN
788        e1f = shift(glamv, -1, 0) - glamt
789        e1f[jpi-1, *] = stepxf[jpi-2, *]
790      ENDELSE
791    ENDIF ELSE e1f = e1u
792;
793    IF jpj EQ 1 THEN e1f = reform(e1f, jpi, jpj, /over)
794;
795;====================================================
796; e2f: y distance between U(i,j) and U(i,j+1)
797;====================================================
798;
799    IF keyword_set(key_irregular) THEN BEGIN
800      e2f = shift(gphiu, 0, -1) - gphiu
801      e2f[*, jpj-1] = e2f[*, jpj-2]
802      IF key_onearth THEN e2f = r * !pi/180. * temporary(e2f)
803    ENDIF ELSE e2f = e2v
804;
805    IF jpj EQ 1 THEN e2f = reform(e2f, jpi, jpj, /over)
806;
807  ENDIF
808;~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
809;
810;
811;====================================================
812; e1[tuvf] from degree to meters
813;====================================================
814;
815  IF keyword_set(key_onearth)  THEN BEGIN
816    e1t = r * !pi/180. * temporary(e1t) * cos(!pi/180.*gphit)
817    IF keyword_set(fullcgrid) THEN BEGIN
818      e1u = r * !pi/180. * temporary(e1u) * cos(!pi/180.*gphiu)
819      e1v = r * !pi/180. * temporary(e1v) * cos(!pi/180.*gphiv)
820      e1f = r * !pi/180. * temporary(e1f) * cos(!pi/180.*gphif)
821    ENDIF
822  ENDIF
823;
824  IF jpj EQ 1 THEN BEGIN
825    e1t = reform(e1t, jpi, jpj, /over)
826    IF keyword_set(fullcgrid) THEN BEGIN
827      e1u = reform(e1u, jpi, jpj, /over)
828      e1v = reform(e1v, jpi, jpj, /over)
829      e1f = reform(e1f, jpi, jpj, /over)
830    ENDIF 
831  ENDIF 
832;
833;====================================================
834; if not fullcgrid: make sure we don't use glam[uv], gphi[uv], e[12][uvf]
835;====================================================
836;
837  IF NOT keyword_set(fullcgrid) THEN BEGIN
838    glamu = !values.f_nan & glamv = !values.f_nan
839    gphiu = !values.f_nan & gphiv = !values.f_nan
840    e1u = !values.f_nan & e1v = !values.f_nan & e1f = !values.f_nan
841    e2u = !values.f_nan & e2v = !values.f_nan & e2f = !values.f_nan
842    firstxu = !values.f_nan & lastxu = !values.f_nan & nxu = !values.f_nan 
843    firstyu = !values.f_nan & lastyu = !values.f_nan & nyu = !values.f_nan 
844    firstxv = !values.f_nan & lastxv = !values.f_nan & nxv = !values.f_nan 
845    firstyv = !values.f_nan & lastyv = !values.f_nan & nyv = !values.f_nan 
846  ENDIF
847;
848;====================================================
849; Z direction
850;====================================================
851;
852; z axis   
853;
854    CASE n_elements(zaxis) OF
855      0:BEGIN
856        gdept = 0.
857        key_zreverse = 0
858      END
859      1:BEGIN
860        gdept = zaxis
861        key_zreverse = 0
862      END
863      ELSE:BEGIN
864        gdept = zaxis[izminmesh:izmaxmesh]
865        IF jpk GT 1 THEN BEGIN
866          if gdept[0] GT gdept[1] then begin
867            gdept = reverse(gdept)
868            key_zreverse = 1
869          ENDIF ELSE key_zreverse = 0
870        ENDIF ELSE key_zreverse = 0
871      END
872    ENDCASE
873;
874    if n_elements(gdept) GT 1 then BEGIN
875      stepz = shift(gdept, -1)-gdept
876      stepz[jpk-1] = stepz[jpk-2]
877      gdepw = 0. > (gdept-stepz/2.)
878    ENDIF ELSE BEGIN
879      stepz = 1.
880      gdepw = gdept
881    ENDELSE
882;
883;====================================================
884; e3[tw]:
885;====================================================
886;
887    e3t = stepz
888    IF n_elements(stepz) GT 1 THEN BEGIN
889      e3w = 0.5*(stepz+shift(stepz, 1))
890      e3w[0] = 0.5*e3t[0]
891    ENDIF ELSE e3w = e3t
892;
893;====================================================
894; Mask
895;====================================================
896;
897; defaut mask eq 1
898  if NOT keyword_set(mask) then mask = -1
899;
900  if mask[0] NE -1 then BEGIN
901    tmask = byte(mask[ixminmesh:ixmaxmesh, iyminmesh:iymaxmesh, izminmesh:izmaxmesh])
902    tmask = reform(tmask, jpi, jpj, jpk, /over)
903    if key_shift NE 0 then tmask = shift(tmask, key_shift, 0, 0)
904; because tmask = reverse(tmask, 2) is not working if the 3rd
905; dimension of tmask = 1, we call reform.
906    IF jpk EQ 1 THEN tmask = reform(tmask, /over)
907    IF key_yreverse EQ 1 THEN tmask = reverse(tmask, 2)
908    IF jpk EQ 1 THEN tmask = reform(tmask, jpi, jpj, jpk, /over)
909    IF key_zreverse EQ 1 THEN tmask = reverse(tmask, 3)
910    IF jpk EQ 1 THEN tmask = reform(tmask, jpi, jpj, jpk, /over)
911    IF keyword_set(fullcgrid) THEN BEGIN
912      IF keyword_set(key_periodic) THEN BEGIN
913        msk = tmask*shift(tmask, -1, 0, 0)
914        umaskred = msk[jpi-1, *, *]
915      ENDIF ELSE umaskred = tmask[jpi-1, *, *]
916      vmaskred = tmask[*, jpj-1, *]
917      fmaskredy = tmask[jpi-1, *, *]
918      fmaskredx = tmask[*, jpj-1, *]
919    ENDIF
920  ENDIF ELSE BEGIN
921    tmask = replicate(1b, jpi, jpj, jpk)
922    IF keyword_set(fullcgrid) THEN BEGIN
923      umaskred  = replicate(1b, jpj, jpk)
924      vmaskred  = replicate(1b, jpi, jpk)
925      fmaskredy = replicate(1b, jpj, jpk)
926      fmaskredx = replicate(1b, jpi, jpk)
927    ENDIF
928  ENDELSE
929;
930  IF jpi GT 2 AND jpj GT 2 AND NOT keyword_set(plain) $
931     AND ixminmesh EQ 0l AND ixmaxmesh eq jpiglo-1 $
932     AND iyminmesh EQ 0l AND iymaxmesh eq jpjglo-1 $
933     AND total(tmask[*, 0, *]) EQ 0 AND total(tmask[*, jpj-1, *]) EQ 0 $
934     AND total(tmask[0, *, *]) EQ 0 AND total(tmask[jpi-1, *, *]) EQ 0 THEN BEGIN
935        xminmesh = 1
936        xmaxmesh = -1
937        yminmesh = 1
938        ymaxmesh = -1
939        computegrid, XAXIS = glamt, YAXIS = gphit, ZAXIS = zaxis $
940                     , MASK = mask, GLAMBOUNDARY = glamboundary $
941                     , XMINMESH = xminmesh, XMAXMESH = xmaxmesh $
942                     , YMINMESH = yminmesh, YMAXMESH = ymaxmesh $
943                     , ZMINMESH = zminmesh, ZMAXMESH = zmaxmesh $
944                     , ONEARTH = onearth, PERIODIC = periodic $
945                     , PLAIN = plain, SHIFT = shift, STRIDE = stride $
946                     , FULLCGRID = fullcgrid, XYINDEX = xyindex $
947                     , FBASE2TBASE = fbase2tbase, STRCALLING = strcalling $
948                     , _extra = ex
949        return
950  ENDIF
951;
952  IF NOT keyword_set(fullcgrid) THEN BEGIN
953    umaskred = !values.f_nan
954    vmaskred = !values.f_nan
955    fmaskredy = !values.f_nan
956    fmaskredx = !values.f_nan
957  ENDIF
958;
959;====================================================
960; stride...
961;====================================================
962;
963  IF total(key_stride) GT 3 THEN BEGIN
964    IF key_shift NE 0 THEN BEGIN
965; for explanation, see header of read_ncdf_varget.pro
966      jpiright = key_shift
967      jpileft = jpi - key_shift - ( (key_stride[0]-1)-((key_shift-1) MOD key_stride[0]) )
968      jpi = ((jpiright-1)/key_stride[0]+1) + ((jpileft-1)/key_stride[0]+1)
969    ENDIF ELSE jpi = (jpi-1)/key_stride[0]+1
970    jpj = (jpj-1)/key_stride[1]+1
971    jpk = (jpk-1)/key_stride[2]+1
972;
973    glamt = (temporary(glamt))[0:*:stride[0], 0:*:stride[1]]
974    gphit = (temporary(gphit))[0:*:stride[0], 0:*:stride[1]]
975    e1t = (temporary(e1t))[0:*:stride[0], 0:*:stride[1]]
976    e2t = (temporary(e2t))[0:*:stride[0], 0:*:stride[1]]
977    tmask = (temporary(tmask))[0:*:stride[0], 0:*:stride[1], 0:*:stride[2]]
978    gdept = gdept[0:*:stride[2]]
979    gdepw = gdepw[0:*:stride[2]]
980    e3t = e3t[0:*:stride[2]]
981    e3w = e3w[0:*:stride[2]]
982; we must recompute glamf and gphif...
983    IF jpi GT 1 THEN BEGIN
984      if (keyword_set(key_onearth) AND keyword_set(xnotsorted)) $
985        OR (keyword_set(key_periodic) AND key_irregular) then BEGIN
986        stepxf = (glamt + 720) MOD 360
987        stepxf = shift(stepxf, -1, -1) - stepxf
988        stepxf = [ [[stepxf]], [[stepxf + 360]], [[stepxf - 360]] ]
989        stepxf = min(abs(stepxf), dimension = 3)
990        IF NOT keyword_set(key_periodic) THEN $
991          stepxf[jpi-1, *] = stepxf[jpi-2, *]
992      ENDIF ELSE BEGIN
993        stepxf = shift(glamt, -1, -1) - glamt
994        IF keyword_set(key_periodic) THEN $
995          stepxf[jpi-1, *] = 360 + stepxf[jpi-1, *] $
996          ELSE stepxf[jpi-1, *] = stepxf[jpi-2, *]
997      ENDELSE
998      IF jpj GT 1 THEN BEGIN
999        stepxf[*, jpj-1] = stepxf[*, jpj-2]
1000        stepxf[jpi-1, jpj-1] = stepxf[jpi-2, jpj-2]
1001      ENDIF
1002      glamf = glamt + 0.5 * stepxf
1003    ENDIF ELSE glamf = glamt + 0.5
1004    IF jpj GT 1 THEN BEGIN
1005; we must compute stepyf: y distance between T(i,j) T(i+1,j+1)
1006      stepyf = shift(gphit, -1, -1) - gphit
1007      stepyf[*, jpj-1] = stepyf[*, jpj-2]
1008      IF jpi GT 1 THEN BEGIN
1009        if NOT keyword_set(key_periodic) THEN $
1010          stepyf[jpi-1, *] = stepyf[jpi-2, *]
1011        stepyf[jpi-1, jpj-1] = stepyf[jpi-2, jpj-2]
1012      ENDIF
1013      gphif = gphit + 0.5 * stepyf
1014    ENDIF ELSE gphif = gphit + 0.5
1015;
1016    IF jpj EQ 1 THEN BEGIN
1017      glamt = reform(glamt, jpi, jpj, /over)
1018      gphit = reform(gphit, jpi, jpj, /over)
1019      glamf = reform(glamf, jpi, jpj, /over)
1020      gphif = reform(gphif, jpi, jpj, /over)
1021      e1t = reform(e1t, jpi, jpj, /over)
1022      e2t = reform(e2t, jpi, jpj, /over)
1023    ENDIF
1024;
1025    IF keyword_set(fullcgrid) THEN BEGIN
1026      glamu = (temporary(glamu))[0:*:stride[0], 0:*:stride[1]]
1027      gphiu = (temporary(gphiu))[0:*:stride[0], 0:*:stride[1]]
1028      e1u = (temporary(e1u))[0:*:stride[0], 0:*:stride[1]]
1029      e2u = (temporary(e2u))[0:*:stride[0], 0:*:stride[1]]
1030      glamv = (temporary(glamv))[0:*:stride[0], 0:*:stride[1]]
1031      gphiv = (temporary(gphiv))[0:*:stride[0], 0:*:stride[1]]
1032      e1v = (temporary(e1v))[0:*:stride[0], 0:*:stride[1]]
1033      e2v = (temporary(e2v))[0:*:stride[0], 0:*:stride[1]]
1034      e1f = (temporary(e1f))[0:*:stride[0], 0:*:stride[1]]
1035      e2f = (temporary(e2f))[0:*:stride[0], 0:*:stride[1]]
1036      umaskred = (temporary(umaskred))[0, 0:*:stride[1], 0:*:stride[2]]
1037      vmaskred = (temporary(vmaskred))[0:*:stride[0], 0, 0:*:stride[2]]
1038      fmaskredy = (temporary(fmaskredy))[0, 0:*:stride[1], 0:*:stride[2]]
1039      fmaskredx = (temporary(fmaskredx))[0:*:stride[0], 0, 0:*:stride[2]]
1040      IF jpj EQ 1 THEN BEGIN
1041        glamu = reform(glamu, jpi, jpj, /over)
1042        gphiu = reform(gphiu, jpi, jpj, /over)
1043        e1u = reform(e1u, jpi, jpj, /over)
1044        e2u = reform(e2u, jpi, jpj, /over)
1045        glamv = reform(glamv, jpi, jpj, /over)
1046        gphiv = reform(gphiv, jpi, jpj, /over)
1047        e1v = reform(e1v, jpi, jpj, /over)
1048        e2v = reform(e2v, jpi, jpj, /over)
1049        e1f = reform(e1f, jpi, jpj, /over)
1050        e2f = reform(e2f, jpi, jpj, /over)
1051      ENDIF
1052    ENDIF
1053  ENDIF
1054;
1055;====================================================
1056; apply all the grid parameters
1057;====================================================
1058;
1059  @updateold
1060  domdef
1061;
1062;====================================================
1063; Triangulation
1064;====================================================
1065;
1066  IF total(tmask) EQ jpi*jpj*jpk $
1067    AND NOT keyword_set(key_irregular) THEN triangles_list = -1 $
1068  ELSE BEGIN
1069; are we using ORCA2 ?
1070    IF jpiglo EQ 182 AND jpi EQ 181 AND jpjglo EQ 149 AND jpj EQ 148 THEN $
1071       triangles_list = triangule() ELSE triangles_list = triangule(/keep_cont)
1072  ENDELSE
1073;
1074;====================================================
1075; time axis (default definition)
1076;====================================================
1077;
1078  IF n_elements(time) EQ 0 OR n_elements(jpt) EQ 0 THEN BEGIN
1079    jpt = 1
1080    time = 0
1081  ENDIF
1082;
1083  IF NOT keyword_set(key_forgetold) THEN BEGIN
1084@updateold
1085  ENDIF
1086;====================================================
1087; grid parameters used by xxx
1088;====================================================
1089;
1090  IF NOT keyword_set(strcalling) THEN BEGIN
1091    IF n_elements(ccmeshparameters) EQ 0 THEN strcalling = 'computegrid' $
1092    ELSE strcalling = ccmeshparameters.filename
1093  ENDIF
1094  IF n_elements(glamt) GE 2 THEN BEGIN
1095    glaminfo = moment(glamt)
1096    IF finite(glaminfo[2]) EQ 0 THEN glaminfo = glaminfo[0:1]
1097    gphiinfo = moment(gphit)
1098    IF finite(gphiinfo[2]) EQ 0 THEN gphiinfo = gphiinfo[0:1]
1099  ENDIF ELSE BEGIN
1100    glaminfo = glamt
1101    gphiinfo = gphit
1102  ENDELSE
1103  ccmeshparameters = {filename:strcalling  $
1104          , glaminfo:float(string(glaminfo, format = '(E11.4)')) $
1105          , gphiinfo:float(string(gphiinfo, format = '(E11.4)')) $
1106          , jpiglo:jpiglo, jpjglo:jpjglo, jpkglo:jpkglo $
1107          , jpi:jpi, jpj:jpj, jpk:jpk $
1108          , ixminmesh:ixminmesh, ixmaxmesh:ixmaxmesh $
1109          , iyminmesh:iyminmesh, iymaxmesh:iymaxmesh $
1110          , izminmesh:izminmesh, izmaxmesh:izmaxmesh $
1111          , key_shift:key_shift, key_periodic:key_periodic $
1112          , key_stride:key_stride, key_gridtype:key_gridtype $
1113          , key_yreverse:key_yreverse, key_zreverse:key_zreverse $
1114          , key_partialstep:key_partialstep, key_onearth:key_onearth}
1115
1116  ccreadparameters = {funclec_name:'read_ncdf' $
1117          , jpidta:jpidta, jpjdta:jpjdta, jpkdta:jpkdta $
1118          , ixmindta:ixmindta, ixmaxdta:ixmaxdta $
1119          , iymindta:iymindta, iymaxdta:iymaxdta $
1120          , izmindta:izmindta, izmaxdta:izmaxdta}
1121;------------------------------------------------------------
1122  IF keyword_set(key_performance) EQ 1 THEN $
1123    print, 'time computegrid', systime(1)-time1
1124;------------------------------------------------------------
1125  return
1126end
1127
Note: See TracBrowser for help on using the repository browser.