source: trunk/SRC/ToBeReviewed/CALCULS/grossemoyenne.pro @ 134

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

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

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 29.7 KB
Line 
1;------------------------------------------------------------
2;------------------------------------------------------------
3;------------------------------------------------------------
4;+
5; NAME: grossemoyenne
6;
7; PURPOSE:  averages a 3- or 4-d time serie field over a selected
8;           geographical area or along the time axis. For one ore more
9;           selected axes (x, y, z, t)
10;
11; CATEGORY:
12;
13; CALLING SEQUENCE: result = grossemoyenne(tab,'direc',BOXZOOM=boxzoom)
14;
15; INPUTS:       tab = 3 or 4d field
16;               direc ='x' 'y' 'z' 't' 'xy' 'xz' 'yz' 'xyz' 'xt' 'yt' 'zt'
17;               'xyt' 'xzt' 'yzt' or 'xyzt'
18;
19; KEYWORD PARAMETERS:
20;
21;               boxzoom = [xmin,xmax,ymin,ymax (,(zmin,)zmax)] pour plus
22;               de detail cf domdef
23;               boxzoom peut prendre 5 formes:
24;               [vert2], [vert1, vert2],[lon1, lon2, lat1, lat2], 
25;               [lon1, lon2, lat1, lat2, vert2],[lon1, lon2, lat1, lat2, vert1,vert2]
26;             
27;               NAN: not a number, a activer si l''on peut faire veut
28;               faire une moyenne sans tenir compte de certaines
29;               valeurs masques de tab.
30;               si les valeurs masques de tab sont la valeur consacree
31;               par IDL (!values.f_nan), il suffit de mettre /NAN.
32;               si les valeurs masques de tab on pour valeur a (a doit
33;               etre differente de 1 (correspond a nan =
34;               !values.f_nan) et de 0 (qui desactive nan).
35;               Il faut mettre NAN=a.
36;               Rq: en sorties les points de result qui sont NAN
37;               auront pour valeur a ou !values.f_nan.
38;           
39;               NODOMDEF: activer si l''on ne veut pas passer ds
40;               domdef bien que le mot cle boxzoom soit present (comme
41;               c''est le cas qd grossemoyenne est appelee via
42;               checkfield)
43;
44;               INTEGRATION: pour faire une integrale plutot qu''une
45;               moyenne
46;
47;               /SPATIALFIRST, when performing at the same time
48;               spatial and temporal mean, grossemoyenne is assuming
49;               that the mask is not changing with the time. In
50;               consequence, grossemoyenne performs temporal mean
51;               first and then call moyenne. Activate /SPATIALFIRST if
52;               you want to perform the spatial mean before the
53;               temporal mean. Note that if NAN is activated, then
54;               SPATIALFIRST is activated automatically.
55;
56;               /TEMPORALFIRST: to force to perform first temporal
57;               mean even if nan is activated (see SPATIALFIRST
58;               explanations...)
59;
60;
61;         /WDEPTH: to specify that the field is at W depth instad of T
62;         depth (automatically activated if vargrid eq 'W')
63;           
64; OUTPUTS:
65;
66; COMMON BLOCKS:   result:un tableau
67;       common    domdef
68;
69; SIDE EFFECTS: met les valeurs correspondants a la terre a 1e20
70;
71; RESTRICTIONS:
72;
73; EXAMPLE:
74;
75; MODIFICATION HISTORY: Jerome Vialard (jv@lodyc.jussieu.fr)
76;                       2/7/98
77;                       Sebastien Masson (smasson@lodyc.jussieu.fr)
78; adaptation pour les tableaux comportants une dimension temporelle
79;                       14/8/98
80;                       15/1/98
81;                       12/3/99 adaptation pour NAN et utilisation de TEMPORARY
82;-
83;------------------------------------------------------------
84;------------------------------------------------------------
85;------------------------------------------------------------
86; PLAN DU PROGRAMME:
87;------------------------------------------------------------
88;------------------------------------------------------------
89;I) preliminaires
90;   I.1) determination des directions de moyennes d''apres direc
91;   I.2) verification de la taille du tableau d''entree
92;   I.3) obtention des facteurs d''echelles et du masque sur le sous
93;   domaine concerne par la moyenne
94;II) moyennes pour les tableaux 3d (x,y,t)
95;   II.1) verification de la coherence de la taille du tableau a
96;   moyenner
97;   II.2) renvoie sur moyenne qd une moyenne sur t est demandee
98;   II.3) differents types de moyennes possibles
99;III) moyennes pour les tableaux 4d (x,y,z,t)
100;   III.1) verification de la coherence de la taille du tableau a
101;   moyenner
102;   III.2) differents types de moyennes possibles
103;IV ) finitions
104;   IV.1) on masque les terres par une valeur a 1e+20
105;   IV.2) on remplace, quand nan ne 1, !values.f_nan par nan
106;   IV.3) on revient au sous domaine initial.
107;------------------------------------------------------------
108;------------------------------------------------------------
109;------------------------------------------------------------
110function grossemoyenne, tab, direc, BOXZOOM = boxzoom, INTEGRATION = integration $
111                        , NAN = nan, NODOMDEF = nodomdef, WDEPTH = wdepth $
112                        , SPATIALFIRST = spatialfirst, TEMPORALFIRST = temporalfirst $
113                        , _extra = ex
114;---------------------------------------------------------
115;
116  compile_opt idl2, strictarrsubs
117;
118@cm_4mesh
119@cm_4data
120@cm_4cal
121  IF NOT keyword_set(key_forgetold) THEN BEGIN
122@updatenew
123@updatekwd
124  ENDIF
125;---------------------------------------------------------
126  tempsun = systime(1)          ; pour key_performance
127;------------------------------------------------------------
128;I) preliminaires
129;------------------------------------------------------------
130  dirt = 0
131  dirx = 0
132  diry = 0
133  dirz = 0
134  dim  = 'aa'
135;------------------------------------------------------------
136; I.1) direction(s) suivants lesquelles on integre
137;------------------------------------------------------------
138  if ( strpos(direc, 't') ge 0 ) then dirt = 1
139  if ( strpos(direc, 'x') ge 0 ) then dirx = 1
140  if ( strpos(direc, 'y') ge 0 ) then diry = 1
141  if ( strpos(direc, 'z') ge 0 ) then dirz = 1
142  IF keyword_set(NAN) AND (dirx EQ 1 OR diry EQ 1 OR dirz EQ 1) $
143    THEN spatialfirst = 1
144  IF keyword_set(temporalfirst) THEN spatialfirst = 0
145;------------------------------------------------------------
146; I.2) verification de la taille du tableau d'entree
147;------------------------------------------------------------
148  taille = size(tab)
149  case 1 of
150    taille[0] eq 1 :return,  report('Le tableau n''a qu''une dimension, cas non traite!')
151    taille[0] eq 2 :return,  report('Le tableau n''a qu''deux dimension, cas non traite!')
152    taille[0] eq 3 :BEGIN
153      dim = '3d'
154      if dirx eq 0 and diry eq 0 and dirt eq 0 then return, tab
155    END
156    taille[0] eq 4 :BEGIN
157      dim = '4d'
158      if dirx eq 0 and diry eq 0 and dirz eq 0 and dirt eq 0 then return, tab
159    END
160    else : return, report('Le tableau d entree doit etre a 3 ou 4 dimensions s''il ne contient pas de dim temporelle utiliser moyenne')
161  endcase
162;------------------------------------------------------------
163;   I.4) obtention des facteurs d''echelles et du masque sur le sous
164;   domaine concerne par la moyenne
165; redefinition du domaine ajuste a boxzoom (a 6 elements)
166; ceci va nous permetre de faire les calcules que sur le sous domaine
167; comcerne par la moyenne. domdef, suivit de grille nous donne tous
168; les tableaux de la grille sur le sous domaine
169;------------------------------------------------------------
170  if keyword_set(boxzoom) then BEGIN
171    Case 1 Of
172      N_Elements(Boxzoom) Eq 1: bte = [lon1, lon2, lat1, lat2, 0., boxzoom[0]]
173      N_Elements(Boxzoom) Eq 2: bte = [lon1, lon2, lat1, lat2, boxzoom[0], boxzoom[1]]
174      N_Elements(Boxzoom) Eq 4: bte = [Boxzoom, vert1, vert2]
175      N_Elements(Boxzoom) Eq 5: bte = [Boxzoom[0:3], 0, Boxzoom[4]]
176      N_Elements(Boxzoom) Eq 6: bte = Boxzoom
177      Else: return, report('Wrong Definition of Boxzoom')
178    endcase
179    if NOT keyword_set(nodomdef) then BEGIN
180      savedbox = 1b
181      saveboxparam, 'boxparam4grmoyenne.dat'
182      domdef, bte, GRIDTYPE = vargrid, _extra = ex
183    ENDIF
184  ENDIF
185;---------------------------------------------------------------
186; attribution du mask et des tableaux de longitude et latitude...
187;---------------------------------------------------------------
188  grille, mask, glam, gphi, gdep, nx, ny, nz, firstx, firsty, firstz, lastx, lasty, lastz, e1, e2, e3, WDEPTH = wdepth
189;------------------------------------------------------------
190; I.3) si dirt eq 1 on fait la moyenne temporelle et on envoie ds moyenne
191;------------------------------------------------------------
192  if dirt EQ 1 AND NOT keyword_set(spatialfirst) then begin
193    if dim EQ 3d then BEGIN
194      case 1 of
195        taille[1] eq jpi and taille[2] eq jpj and taille[3] eq jpt: $
196          res = tab[firstx:firstx+nx-1 $
197                    , firsty:firsty+ny-1, *]
198        taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq jpt:res = tab
199        else:BEGIN
200          if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
201          return, report('Probleme d''adequation entre les tailles du domaine nx*ny*jpt '+strtrim(nx, 1)+'*'+strtrim(ny, 1)+'*'+strtrim(jpt, 1)+' et du tableau '+strtrim(taille[1], 1)+'*'+strtrim(taille[2], 1)+'*'+strtrim(taille[3], 1))
202        END
203      ENDCASE
204      if keyword_set(integration) then begin
205        res = total(res, 3, nan = nan)
206      ENDIF ELSE BEGIN
207        if keyword_set(nan) then BEGIN
208          divi = finite(res)
209          divi = total(temporary(divi), 3)
210          notanum = where(divi EQ 0)
211          res = total(res, 3, nan = keyword_set(nan))/ (1 > divi)
212          if notanum[0] NE -1 then res[temporary(notanum)] = !values.f_nan
213        ENDIF ELSE res = total(res, 3)/(1.*taille[3])
214      ENDELSE
215    ENDIF ELSE BEGIN
216      case 1 of
217        taille[1] eq jpi and taille[2] eq jpj and taille[3] eq jpk and taille[4] eq jpt: $
218          res = tab[firstx:lastx, firsty:lasty, firstz:lastz, *]
219        taille[1] eq jpi and taille[2] eq jpj and taille[3] eq nz and taille[4] eq jpt: $
220          res = tab[firstx:lastx, firsty:lasty, *, *]
221        taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq nz and taille[4] eq jpt:res = tab
222        taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq jpk and taille[4] eq jpt: $
223          res = tab[*, *, firstz:lastz, *]
224        else:BEGIN
225           if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
226          return, report('Probleme d''adequation entre les tailles du domaine nx*ny*nz*jpt ' $
227                         +strtrim(nx, 1)+'*'+strtrim(ny, 1)+'*'+strtrim(nz, 1)+'*' $
228                         +strtrim(jpt, 1)+' et du tableau '+strtrim(taille[1], 1)+'*' $
229                         +strtrim(taille[2], 1)+'*'+strtrim(taille[3], 1)+'*' $
230                         +strtrim(taille[4], 1))
231        END
232        endcase
233      if keyword_set(integration) then begin
234        res = total(res, 4, nan = nan)
235      ENDIF ELSE BEGIN
236        if keyword_set(nan) then begin
237          divi = finite(res)
238          divi = total(temporary(divi), 4)
239          notanum = where(divi EQ 0)
240          res = total(res, 4, /nan)/(1 > divi)
241          if notanum[0] NE -1 then res[temporary(notanum)] = !values.f_nan
242        ENDIF ELSE res = total(res, 4)/(1.*taille[4])
243      ENDELSE
244    ENDELSE
245    if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'   
246    return,  moyenne(temporary(res), direc, BOXZOOM = boxzoom, NAN = nan, INTEGRATION = integration, NODOMDEF = nodomdef, WDEPTH = wdepth, _extra = ex)
247  ENDIF ELSE res = tab
248  IF jpt EQ 1 THEN BEGIN
249    if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'   
250    return, moyenne(reform(res, /over), direc, BOXZOOM = boxzoom, NAN = nan, INTEGRATION = integration, NODOMDEF = nodomdef, WDEPTH = wdepth, _extra = ex)
251  END
252;------------------------------------------------------------
253;------------------------------------------------------------
254; II) Cas serie tableaux 2d (tab3d)
255;------------------------------------------------------------
256;------------------------------------------------------------
257  if (dim eq '3d') then begin
258;---------------------------------------------------------------
259;   II.1) verification de la coherence de la taille du tableau a
260;   moyenner
261; verification de la coherence entre la taille du tableau et le
262; domaine definit par domdef
263; le tableau en entree doit avoir soit la taille du domaine total
264; (jpi,jpj,jpt) soit celle du domaine reduit (nx,ny,jpt)
265;---------------------------------------------------------------
266    case 1 of
267      taille[1] eq jpi and taille[2] eq jpj and taille[3] eq jpt: $
268        res = tab[firstx:firstx+nx-1 $
269                  , firsty:firsty+ny-1, *]
270      taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq jpt:res = tab
271      else:BEGIN
272        if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
273        return, report('Probleme d''adequation entre les tailles du domaine nx*ny*jpt '+strtrim(nx, 1)+'*'+strtrim(ny, 1)+'*'+strtrim(jpt, 1)+' et du tableau '+strtrim(taille[1], 1)+'*'+strtrim(taille[2], 1)+'*'+strtrim(taille[3], 1))
274      enD
275    endcase
276    if keyword_set(nan) NE 0 then BEGIN
277      if nan NE 1 then BEGIN    ; si nan n''est pas !values.f_nan
278; on le met a !values.f_nan
279        if abs(nan) LT 1e6 then notanumber = where(res EQ nan) $
280        ELSE notanumber = where(abs(res) GT abs(nan)/10.)
281        if notanumber[0] NE -1 then res[temporary(notanumber)] = !values.f_nan
282      ENDIF
283    ENDIF
284;---------------------------------------------------------------
285; rq IL FAUT FAIRE ATTENTION AUX CAS OU LA DIM A MOYENNER = 1, ET
286; S'ASSURER QU'ELLE EXISTE BIEN. D'OU LES reform(...,nx,ny,...) QUI
287; PEUVENT SEMBLER INUTILE AU DEPART
288;---------------------------------------------------------------
289    if nx EQ 1 OR ny EQ 1 then BEGIN
290      res = reform(res, nx, ny, jpt, /over)
291      e1 =  reform(e1, nx, ny, /over)
292      e2 =  reform(e2, nx, ny, /over)
293    endif
294    if nx EQ 1 OR ny EQ 1 OR nz EQ 1 THEN $
295      mask =  reform(mask, nx, ny, nz, /over)
296;---------------------------------------------------------------
297; II.3) differents types de moyennes
298;---------------------------------------------------------------
299    if keyword_set(nan) NE 0 then msknan = finite(res) ELSE msknan = -1
300    mask = mask[*, *, 0]
301    case 1 of
302      (dirx eq 1) and (diry eq 0) : begin
303        e = temporary(e1)*temporary(mask)
304        echelle = (temporary(e))[*]#replicate(1, jpt)
305        echelle = reform(echelle, nx, ny, jpt, /over)
306        if keyword_set(integration) then divi = 1 ELSE BEGIN
307          IF msknan[0] NE -1 THEN divi = total(echelle*msknan, 1) $
308          ELSE divi = total(echelle, 1)
309        ENDELSE
310        res = total(temporary(res)*echelle, 1, nan = nan)/(divi > 1.)
311        if msknan[0] NE -1 then BEGIN
312          echelle = temporary(echelle) NE 0
313          testnan = temporary(msknan)*echelle
314          testnan = total(temporary(testnan), 1) $
315            +(total(temporary(echelle), 1) EQ 0)
316        endif
317      end
318      (dirx eq 0) and (diry eq 1) : begin
319        e = temporary(e2)*temporary(mask)
320        if nx EQ 1 OR ny EQ 1 then e = reform(e, nx, ny, /over)
321        echelle = (temporary(e))[*]#replicate(1, jpt)
322        echelle = reform(echelle, nx, ny, jpt, /over)
323        if keyword_set(integration) then divi = 1 ELSE BEGIN
324          IF msknan[0] NE -1 THEN divi = total(echelle*msknan, 2) $
325          ELSE divi = total(echelle, 2)
326        ENDELSE
327        res = total(temporary(res)*echelle, 2, nan = nan)/(divi > 1.)
328        if msknan[0] NE -1 then begin
329          echelle = temporary(echelle) NE 0
330          testnan = temporary(msknan)*echelle
331          testnan = total(temporary(testnan), 2) $
332            +(total(temporary(echelle), 2) EQ 0)
333        endif
334      end
335      (dirx eq 1) and (diry eq 1) : begin
336        echelle = (temporary(e1)*temporary(e2)*temporary(mask))[*]#replicate(1, jpt)
337        echelle = reform(echelle, nx, ny, jpt, /over)
338        if keyword_set(integration) then divi = 1 ELSE BEGIN
339          IF msknan[0] NE -1 THEN divi = total(total(echelle*msknan, 1), 1) $
340          ELSE divi = total(total(echelle, 1), 1)
341        ENDELSE
342        res = total(temporary(total(temporary(res)*echelle, 1, nan = nan)), 1, nan = nan)/(divi > 1.)
343        if msknan[0] NE -1 then begin
344          echelle = temporary(echelle) NE 0
345          testnan = temporary(msknan)*echelle
346          testnan = total(total(temporary(testnan), 1), 1) $
347            +(total(total(temporary(echelle), 1), 1) EQ 0)
348        endif
349      end
350    endcase
351  endif
352;------------------------------------------------------------
353;------------------------------------------------------------
354; III) Cas serie tableaux 3d (tab4d)
355;------------------------------------------------------------
356  if (dim eq '4d') then begin
357;---------------------------------------------------------------
358; III.1) verification de la coherence de la taille du tableau a
359; moyenner
360; verification de la coherence entre la taille du tableau et le
361; domaine definit par domdef
362; le tableau en entree doit avoir soit la taille du domaine total
363; (jpi,jpj,jpk,jpt) soit celle du domaine reduit (nx,ny,ny,jpt)
364;---------------------------------------------------------------
365    case 1 of
366      taille[1] eq jpi and taille[2] eq jpj and taille[3] eq jpk and taille[4] eq jpt: $
367        res = tab[firstx:lastx, firsty:lasty, firstz:lastz, *]
368      taille[1] eq jpi and taille[2] eq jpj and taille[3] eq nz and taille[4] eq jpt: $
369        res = tab[firstx:lastx, firsty:lasty, *, *]
370      taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq nz and taille[4] eq jpt:res = tab
371      taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq jpk and taille[4] eq jpt: $
372        res = tab[*, *, firstz:lastz, *]
373      else:BEGIN
374        if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
375        return, report('Probleme d''adequation entre les tailles du domaine nx*ny*nz*jpt ' $
376                       +strtrim(nx, 1)+'*'+strtrim(ny, 1)+'*'+strtrim(nz, 1)+'*' $
377                       +strtrim(jpt, 1)+' et du tableau '+strtrim(taille[1], 1)+'*' $
378                       +strtrim(taille[2], 1)+'*'+strtrim(taille[3], 1)+'*' $
379                       +strtrim(taille[4], 1))
380      END
381    endcase
382    if nx EQ 1 OR ny EQ 1 OR nz EQ 1 OR jpt EQ 1 then res = reform(res, nx, ny, nz, jpt, /over)
383    if keyword_set(nan) NE 0 then BEGIN
384      if nan NE 1 then BEGIN    ; si nan n''est pas !values.f_nan
385; on le met a !values.f_nan
386        if abs(nan) LT 1e6 then notanumber = where(res EQ nan) $
387        ELSE notanumber = where(abs(res) GT abs(nan)/10.)
388        if notanumber[0] NE -1 then res[temporary(notanumber)] = !values.f_nan
389      ENDIF
390    ENDIF
391;---------------------------------------------------------------
392; rq IL FAUT FAIRE ATTENTION AUX CAS OU LA DIM A MOYENNER = 1, ET
393; S'ASSURER QU'ELLE EXISTE BIEN. D'OU LES reform(...,nx,ny,...) QUI
394; PEUVENT SEMBLER INUTILE AU DEPART
395;---------------------------------------------------------------
396    if nx EQ 1 OR ny EQ 1 OR nz EQ 1 then BEGIN
397      res = reform(res, nx, ny, nz, jpt, /over)
398      mask =  reform(mask, nx, ny, nz, /over)
399    ENDIF
400    IF keyword_set(key_partialstep) THEN BEGIN
401; the top of the ocean floor is
402      IF vargrid EQ 'T' OR vargrid EQ 'W' THEN bottom = total(mask, 3) $
403      ELSE bottom = total(tmask[firstx:lastx, firsty:lasty, firstz:lastz], 3)
404; we suppress columns with only ocean or land
405      good = where(bottom NE 0 AND bottom NE nz)
406; the bottom of the ocean in 3D index is:
407      bottom = lindgen(nx*ny)+(temporary(bottom)-1L)*nx*ny
408      IF good[0] NE -1 THEN bottom = bottom[good] $
409      ELSE bottom = -1
410    ENDIF ELSE bottom = -1
411;---------------------------------------------------------------
412; III.2) differents types de moyennes
413;---------------------------------------------------------------
414    IF keyword_set(nan) NE 0 THEN msknan = finite(res) ELSE msknan = -1
415    case 1 of
416      (dirx eq 1) and (diry eq 0) and (dirz eq 0) : BEGIN
417        e13 = (temporary(e1))[*]#replicate(1., nz)
418        e13 = reform(e13, nx, ny, nz, /over)
419        echelle = (temporary(e13)*temporary(mask))[*]#replicate(1, jpt)
420        echelle = reform(echelle, nx, ny, nz, jpt, /over)
421        IF keyword_set(key_partialstep) AND bottom[0] NE -1 $
422          AND nx NE 1 THEN BEGIN
423          IF msknan[0] EQ -1 THEN BEGIN
424            msknan = replicate(1b, nx, ny, nz, jpt)
425            nan = 1
426          ENDIF
427          bottom = bottom#replicate(1, jpt) $ ; 4D bottom!
428            + replicate(1, n_elements(bottom))#(nx*ny*nz*lindgen(jpt))
429          msknan[bottom] = 0
430          res[temporary(bottom)] = !values.f_nan
431        ENDIF
432        if keyword_set(integration) then divi = 1 ELSE begin
433          IF msknan[0] NE -1 THEN divi = total(echelle*msknan, 1) $
434          ELSE divi = total(echelle, 1)
435        endelse
436        res = temporary(res)*echelle
437        res = total(temporary(res), 1, nan = nan)/(divi > 1)
438        if msknan[0] NE -1 then begin
439          echelle = temporary(echelle) NE 0
440          testnan = temporary(msknan)*echelle
441          testnan = total(temporary(testnan), 1) $
442            +(total(temporary(echelle), 1) EQ 0)
443        endif
444      end
445      (dirx eq 0) and (diry eq 1) and (dirz eq 0) : begin
446        e23 = temporary(e2[*])#replicate(1., nz)
447        e23 = reform(e23, nx, ny, nz, /over)
448        echelle = (temporary(e23)*temporary(mask))[*]#replicate(1, jpt)
449        echelle = reform(echelle, nx, ny, nz, jpt, /over)
450        IF keyword_set(key_partialstep) AND bottom[0] NE -1 $
451          AND ny NE 1 THEN BEGIN
452          IF msknan[0] EQ -1 THEN BEGIN
453            msknan = replicate(1b, nx, ny, nz)
454            nan = 1
455          endif
456          bottom = bottom#replicate(1, jpt) $ ; 4D bottom!
457            + replicate(1, n_elements(bottom))#(nx*ny*nz*lindgen(jpt))
458          msknan[bottom] = 0
459          res[temporary(bottom)] = !values.f_nan
460        ENDIF
461        if keyword_set(integration) then divi = 1 ELSE begin
462          IF msknan[0] NE -1 THEN divi = total(echelle*msknan, 2) $
463          ELSE divi = total(echelle, 2)
464        endelse
465        res = total(temporary(res)*echelle, 2, nan = nan)/(divi > 1)
466        if msknan[0] NE -1 then begin
467          echelle = temporary(echelle) NE 0
468          testnan = temporary(msknan)*echelle
469          testnan = total(temporary(testnan), 2) $
470            +(total(temporary(echelle), 2) EQ 0)
471        endif
472      end
473      (dirx eq 0) and (diry eq 0) and (dirz eq 1) : begin
474        e33 = replicate(1, 1.*nx*ny)#e3
475        e33 = reform(e33, nx, ny, nz, /over)
476        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
477          IF keyword_set(wdepth) THEN $
478            e33[bottom] = (e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
479          ELSE e33[bottom] = (e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
480        ENDIF
481        echelle = (temporary(e33)*temporary(mask))[*]#replicate(1, jpt)
482        echelle = reform(echelle, nx, ny, nz, jpt, /over)
483        if keyword_set(integration) then divi = 1 ELSE begin
484          IF msknan[0] NE -1 THEN divi = total(echelle*msknan, 3) $
485          ELSE divi = total(echelle, 3)
486        endelse
487        res = total(temporary(res)*echelle, 3, nan = nan)/(divi > 1)
488        if msknan[0] NE -1 then begin
489          echelle = temporary(echelle) NE 0
490          testnan = temporary(msknan)*echelle
491          testnan = total(temporary(testnan), 3) $
492            +(total(temporary(echelle), 3) EQ 0)
493        endif
494      end
495      (dirx eq 1) and (diry eq 1) and (dirz eq 0) : begin
496        e13 = e1[*]#replicate(1., nz)
497        e13 = reform(e13, nx, ny, nz, /over)
498        e23 = e2[*]#replicate(1., nz)
499        e23 = reform(e23, nx, ny, nz, /over)
500        echelle = (temporary(e13)*temporary(e23)*temporary(mask))[*]#replicate(1, jpt)
501        echelle = reform(echelle, nx, ny, nz, jpt, /over)
502        IF keyword_set(key_partialstep) AND bottom[0] NE -1 $
503          AND nx*ny NE 1 THEN BEGIN
504          IF msknan[0] EQ -1 THEN BEGIN
505            msknan = replicate(1b, nx, ny, nz)
506            nan = 1
507          endif
508          bottom = bottom#replicate(1, jpt) $ ; 4D bottom!
509            + replicate(1, n_elements(bottom))#(nx*ny*nz*lindgen(jpt))
510          msknan[bottom] = 0
511          res[temporary(bottom)] = !values.f_nan
512        ENDIF
513        if keyword_set(integration) then divi = 1 ELSE begin
514          IF msknan[0] NE -1 THEN divi = total(total(echelle*msknan, 1), 1) $
515          ELSE divi = total(total(echelle, 1), 1)
516        endelse
517        res = total(total(temporary(res)*echelle, 1, nan = nan), 1, nan = nan)/(divi > 1)
518        if msknan[0] NE -1 then begin
519          echelle = temporary(echelle) NE 0
520          testnan = temporary(msknan)*echelle
521          testnan = total(total(temporary(testnan), 1), 1) $
522            +(total(total(temporary(echelle), 1), 1) EQ 0)
523        endif
524      end
525      (dirx eq 1) and (diry eq 0) and (dirz eq 1) : begin
526        e133 = e1[*]#e3
527        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
528          IF keyword_set(wdepth) THEN $
529            e133[bottom] = (e1*e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
530          ELSE e133[bottom] = (e1*e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
531        ENDIF
532        echelle = (temporary(e133[*])*temporary(mask[*]))#replicate(1, jpt)
533        echelle = reform(echelle, nx, ny, nz, jpt, /over)
534        if keyword_set(integration) then divi = 1 ELSE begin
535          IF msknan[0] NE -1 THEN divi = total(total(echelle*msknan, 1), 2) $
536          ELSE divi = total(total(echelle, 1), 2)
537        endelse
538        res = total(total(temporary(res)*echelle, 1, nan = nan), 2, nan = nan)/(divi > 1)
539        if msknan[0] NE -1 then begin
540          echelle = temporary(echelle) NE 0
541          testnan = temporary(msknan)*echelle
542          testnan = total(total(temporary(testnan), 1), 2) $
543            +(total(total(temporary(echelle), 1), 2) EQ 0)
544        endif
545      end
546      (dirx eq 0) and (diry eq 1) and (dirz eq 1) : begin
547        e233 = e2[*]#e3
548        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
549          IF keyword_set(wdepth) THEN $
550            e233[bottom] = (e2*e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
551          ELSE e233[bottom] = (e2*e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
552        ENDIF
553        echelle = (temporary(e233[*])*temporary(mask[*]))#replicate(1, jpt)
554        echelle = reform(echelle, nx, ny, nz, jpt, /over)
555        if keyword_set(integration) then divi = 1 ELSE begin
556          IF msknan[0] NE -1 THEN divi = total(total(echelle*msknan, 2), 2) $
557          ELSE divi = total(total(echelle, 2), 2)
558        endelse
559        res = total(total(temporary(res)*echelle, 2, nan = nan), 2, nan = nan)/(divi > 1)
560        if msknan[0] NE -1 then begin
561          echelle = temporary(echelle) NE 0
562          testnan = temporary(msknan)*echelle
563          testnan = total(total(temporary(testnan), 2), 2) $
564            +(total(total(temporary(echelle), 2), 2) EQ 0)
565        endif
566      end
567      (dirx eq 1) and (diry eq 1) and (dirz eq 1) : begin
568        e1233 = (e1[*]*e2[*])#e3
569        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
570          IF keyword_set(wdepth) THEN $
571            e1233[bottom] = (e1*e2*e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
572          ELSE e1233[bottom] = (e1*e2*e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
573        ENDIF
574        echelle = (temporary(e1233[*])*temporary(mask[*]))#replicate(1, jpt)
575        echelle = reform(echelle, nx, ny, nz, jpt, /over)
576        if keyword_set(integration) then divi = 1 ELSE begin
577          IF msknan[0] NE -1 THEN divi = total(total(total(echelle*msknan, 1), 1), 1) $
578          ELSE divi = total(total(total(echelle, 1), 1), 1)
579        endelse
580        res = total(total(total(temporary(res)*echelle, 1, nan = nan), 1, nan = nan), 1, nan = nan)/(divi > 1)
581        if msknan[0] NE -1 then begin
582          echelle = temporary(echelle) NE 0
583          testnan = temporary(msknan)*echelle
584          testnan = total(total(total(temporary(testnan), 1), 1), 1) $
585            +(total(total(total(temporary(echelle), 1), 1), 1) EQ 0)
586        endif
587      end
588    endcase
589  endif
590;------------------------------------------------------------
591  if dirt EQ 1 AND keyword_set(spatialfirst) then BEGIN
592    IF (reverse(size(res, /dimension)))[0] NE jpt THEN BEGIN
593      print, 'the last dimension of res is not equal to jpt: '+strtrim(jpt, 2)
594      if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
595      return, -1
596    ENDIF
597    tdim = size(res, /n_dimensions)
598    if keyword_set(integration) then res = total(res, tdim, nan = nan) $
599    ELSE BEGIN
600      if keyword_set(nan) then BEGIN
601        testnan = testnan < 1
602        testnan = total(temporary(testnan), tdim)
603        divi = testnan
604      ENDIF ELSE divi = jpt
605      res = total(res, tdim, nan = nan)/(1 > divi)
606    ENDELSE
607  ENDIF
608;------------------------------------------------------------
609;------------------------------------------------------------
610;IV ) finitions
611;------------------------------------------------------------
612;------------------------------------------------------------
613; IV.1) on masque les terres par une valeur a 1e+20
614;------------------------------------------------------------
615  valmask = 1e+20
616  terre = where(divi EQ 0)
617  IF terre[0] NE -1 THEN BEGIN
618    res[temporary(terre)] = 1e+20
619  ENDIF
620;------------------------------------------------------------
621; IV.2) on remplace, quand nan ne 1, !values.f_nan par nan
622;------------------------------------------------------------
623  if keyword_set(nan) NE 0 then BEGIN
624    puttonan = where(temporary(testnan) EQ 0)
625    if puttonan[0] NE -1 then res[temporary(puttonan)] = !values.f_nan
626    if nan NE 1 then BEGIN
627      notanumber = where(finite(res) eq 0)
628      if notanumber[0] NE -1 then res[temporary(notanumber)] = nan
629    ENDIF
630  ENDIF
631;------------------------------------------------------------
632; IV.3) on se remplace ds le sous domaine qui etait definit a l''entree de
633; moyenne
634;------------------------------------------------------------
635  if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
636;------------------------------------------------------------
637  if keyword_set(key_performance) THEN print, 'temps grossemoyenne', systime(1)-tempsun
638  return, res
639;------------------------------------------------------------
640;------------------------------------------------------------
641end
Note: See TracBrowser for help on using the repository browser.