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

Last change on this file since 442 was 442, checked in by smasson, 14 years ago

add mask2d keyword in moyenne and grossemoyenne

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 29.5 KB
Line 
1;+
2;
3; @file_comments
4; averages a 3- or 4-d time series field over a selected
5; geographical area or along the time axis. For one or more
6; selected axes (x, y, z, t)
7;
8; @categories
9;
10; @param TAB {in}{required}
11; 3d or 4d field
12;
13; @param DIREC {in}{required}
14; 'x' 'y' 'z' 't' 'xy' 'xz' 'yz' 'xyz' 'xt' 'yt' 'zt'
15; 'xyt' 'xzt' 'yzt' or 'xyzt'
16;
17; @keyword BOXZOOM
18; [xmin,xmax,ymin,ymax (,(zmin,)zmax)] to more details, see <pro>domdef</pro>
19; boxzoom can have 5 forms :
20; [vert2], [vert1, vert2],[lon1, lon2, lat1, lat2],
21; [lon1, lon2, lat1, lat2, vert2],[lon1, lon2, lat1, lat2, vert1,vert2]
22;
23; @keyword KEEPBOTTOM {default=0}{type=scalar: 0 or 1}
24; used only with partial steps (key_partialstep /= 0). In partial
25; steps, bottom points are not located at the same depth => they
26; should not be averaged together along x and/or y direction if there
27; is no average along z. In this case bottom ponts are set to
28;!values.f_nan before doing any call to total.
29;
30; @keyword NAN
31; not a number, we activate it if we want to average without considerate some
32; masked values of TAB.
33; If masked values of TAB are values consecrated by IDL(!values.f_nan), we
34; just have to put NAN.
35; If masked values of TAB are valued a (a must be different of 1,
36; corresponding to nan = !values.f_nan and of 0, which desactivate nan).
37; We have to put NAN=a.
38; Comment: In output, result points which are NAN will be valued a or
39; !values.f_nan.
40;
41; @keyword NODOMDEF
42; We activate it if we do not want to pass in <pro>domdef</pro> even if the
43; keyword boxzoom is present (like when <pro>grossemoyenne</pro> is called via
44; <pro>checkfield</pro>)
45;
46; @keyword INTEGRATION
47; To make an integral rather than an average
48;
49; @keyword MASK2D
50; an optional 2d mask array (containing only 0 and 1) that can be use
51; to modified each levels of the default mask.
52;
53; @keyword SPATIALFIRST
54; when performing at the same time
55; spatial and temporal mean, grossemoyenne is assuming
56; that the mask is not changing with the time. In
57; consequence, grossemoyenne performs temporal mean
58; first and then call moyenne. Activate /SPATIALFIRST if
59; you want to perform the spatial mean before the
60; temporal mean. Note that if NAN is activated, then
61; SPATIALFIRST is activated automatically.
62;
63; @keyword TEMPORALFIRST
64; to force to perform first temporal
65; mean even if NAN is activated (see SPATIALFIRST explanations...)
66;
67; @keyword SSH
68; array giving the sea level elenation (in meter) that must be added
69; to the thickness of the first level when computing vertical mean
70;
71; @keyword WDEPTH
72; to specify that the field is at W depth instead of T
73; depth (automatically activated if vargrid eq 'W')
74;
75; @returns
76; an array
77;
78; @uses
79; <pro>common</pro>
80; <pro>domdef</pro>
81;
82; @restrictions
83; Put values corresponding to land at 1.e20
84;
85; @history
86; Jerome Vialard (jv\@lodyc.jussieu.fr)
87;                       2/7/98
88;                       Sebastien Masson (smasson\@lodyc.jussieu.fr)
89; adaptation array containing a temporal dimension
90;                       14/8/98
91;                       15/1/98
92;                       12/3/99 adaptation for NAN and utilization of TEMPORARY
93;
94; @version
95; $Id$
96;
97;-
98FUNCTION grossemoyenne, tab, direc, BOXZOOM=boxzoom, INTEGRATION=integration, KEEPBOTTOM = keepbottom $
99                      , NAN=nan, NODOMDEF=nodomdef, WDEPTH=wdepth, SSH=ssh, MASK2D=mask2d $
100                      , SPATIALFIRST=spatialfirst, TEMPORALFIRST=temporalfirst $
101                      , _EXTRA=ex
102;
103  compile_opt idl2, strictarrsubs
104;
105@cm_4mesh
106@cm_4data
107@cm_4cal
108  IF NOT keyword_set(key_forgetold) THEN BEGIN
109@updatenew
110@updatekwd
111  ENDIF
112;---------------------------------------------------------
113  tempsun = systime(1)          ; For key_performance
114;------------------------------------------------------------
115;I) preliminaries
116;------------------------------------------------------------
117  dirt = 0
118  dirx = 0
119  diry = 0
120  dirz = 0
121  dim  = 'aa'
122;------------------------------------------------------------
123; I.1) Directions(s) we follow to integrate
124;------------------------------------------------------------
125  if ( strpos(direc, 't') ge 0 ) then dirt = 1
126  if ( strpos(direc, 'x') ge 0 ) then dirx = 1
127  if ( strpos(direc, 'y') ge 0 ) then diry = 1
128  if ( strpos(direc, 'z') ge 0 ) then dirz = 1
129  IF keyword_set(NAN) AND (dirx EQ 1 OR diry EQ 1 OR dirz EQ 1) $
130    THEN spatialfirst = 1
131  IF keyword_set(temporalfirst) THEN spatialfirst = 0
132;------------------------------------------------------------
133; I.2) verification of the input array's size
134;------------------------------------------------------------
135  taille = size(tab)
136  case 1 of
137    taille[0] eq 1 :return,  report('array has only one dimension, not implemented!')
138    taille[0] eq 2 :return,  report('array has only two dimensions, not implemented!')
139    taille[0] eq 3 :BEGIN
140      dim = '3d'
141      if dirx eq 0 and diry eq 0 and dirt eq 0 then return, tab
142    END
143    taille[0] eq 4 :BEGIN
144      dim = '4d'
145      if dirx eq 0 and diry eq 0 and dirz eq 0 and dirt eq 0 then return, tab
146    END
147    else : return, report('array must have 3 or 4 dimensions if there is not time dimension use moyenne')
148  endcase
149;------------------------------------------------------------
150;   I.3) Obtainment of scale's factors and of the mask on the subdomain concernedby the average.
151; Redefinition of the domain ajusted at boxzoom (at 6 elements)
152; This will allowed us to calculate only in the domain concerned by the average.
153; Domdef, followed by grid give us all arrays of the grid on the subdomain
154;------------------------------------------------------------
155  if keyword_set(boxzoom) then BEGIN
156    Case 1 Of
157      N_Elements(Boxzoom) Eq 1: bte = [lon1, lon2, lat1, lat2, 0., boxzoom[0]]
158      N_Elements(Boxzoom) Eq 2: bte = [lon1, lon2, lat1, lat2, boxzoom[0], boxzoom[1]]
159      N_Elements(Boxzoom) Eq 4: bte = [Boxzoom, vert1, vert2]
160      N_Elements(Boxzoom) Eq 5: bte = [Boxzoom[0:3], 0, Boxzoom[4]]
161      N_Elements(Boxzoom) Eq 6: bte = Boxzoom
162      Else: return, report('Wrong Definition of Boxzoom')
163    endcase
164    if NOT keyword_set(nodomdef) then BEGIN
165      savedbox = 1b
166      saveboxparam, 'boxparam4grmoyenne.dat'
167      domdef, bte, GRIDTYPE = vargrid, _extra = ex
168    ENDIF
169  ENDIF
170;---------------------------------------------------------------
171; attribution of the mask and of longitude and latitude arrays...
172;---------------------------------------------------------------
173  grille, mask, glam, gphi, gdep, nx, ny, nz, firstx, firsty, firstz, lastx, lasty, lastz, e1, e2, e3, WDEPTH = wdepth
174  IF keyword_set(mask2D) THEN BEGIN
175    IF taille[1] eq jpi and taille[2] eq jpj THEN $
176       mmm = mask2D[firstx:lastx, firsty:lasty] ELSE mmm = mask2D
177    mask = mask * ( mmm[*] # replicate(1., nz) )
178  ENDIF
179;---------------------------------------------------------------
180; check the use of ssh keyword...
181;---------------------------------------------------------------
182  IF keyword_set(ssh) AND dirz NE 0 AND firstz EQ 0 AND taille[0] GT 2 THEN BEGIN
183    IF vargrid NE 'T' THEN return, report('use of ssh keywords is coded only for T point case...')
184    szssh = size(ssh)
185    IF szssh[1] NE taille[1] OR szssh[2] NE taille[2] THEN $
186       return, report('ssh and input arrays must have the same size')
187    IF taille[1] eq jpi and taille[2] eq jpj THEN $
188       sshh = ssh[firstx:lastx, firsty:lasty,*] ELSE sshh = ssh
189    sshh = sshh * ( (mask[*,*,0])[*] # replicate(1., jpt) )
190  ENDIF
191;------------------------------------------------------------
192; I.4) if dirt equal 1, we make the temporal average and we send it in moyenne
193;------------------------------------------------------------
194  if dirt EQ 1 AND NOT keyword_set(spatialfirst) then BEGIN
195    IF keyword_set(sshh) THEN return, report('ssh and temporal mean: case not coded...')
196    if dim EQ 3d then BEGIN
197      case 1 of
198        taille[1] eq jpi and taille[2] eq jpj and taille[3] eq jpt: $
199          res = tab[firstx:firstx+nx-1, firsty:firsty+ny-1, *]
200        taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq jpt:res = tab
201        else:BEGIN
202          if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
203          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))
204        END
205      ENDCASE
206      if keyword_set(integration) then begin
207        res = total(res, 3, nan = nan)
208      ENDIF ELSE BEGIN
209        if keyword_set(nan) then BEGIN
210          divi = finite(res)
211          divi = total(temporary(divi), 3)
212          notanum = where(divi EQ 0)
213          res = total(res, 3, nan = keyword_set(nan))/ (1 > divi)
214          if notanum[0] NE -1 then res[temporary(notanum)] = !values.f_nan
215        ENDIF ELSE res = total(res, 3)/(1.*taille[3])
216      ENDELSE
217    ENDIF ELSE BEGIN
218      case 1 of
219        taille[1] eq jpi and taille[2] eq jpj and taille[3] eq jpk and taille[4] eq jpt: $
220          res = tab[firstx:lastx, firsty:lasty, firstz:lastz, *]
221        taille[1] eq jpi and taille[2] eq jpj and taille[3] eq nz and taille[4] eq jpt: $
222          res = tab[firstx:lastx, firsty:lasty, *, *]
223        taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq nz and taille[4] eq jpt:res = tab
224        taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq jpk and taille[4] eq jpt: $
225          res = tab[*, *, firstz:lastz, *]
226        else:BEGIN
227           if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
228          return, report('Probleme d''adequation entre les tailles du domaine nx*ny*nz*jpt ' $
229                         +strtrim(nx, 1)+'*'+strtrim(ny, 1)+'*'+strtrim(nz, 1)+'*' $
230                         +strtrim(jpt, 1)+' et du tableau '+strtrim(taille[1], 1)+'*' $
231                         +strtrim(taille[2], 1)+'*'+strtrim(taille[3], 1)+'*' $
232                         +strtrim(taille[4], 1))
233        END
234        endcase
235      if keyword_set(integration) then begin
236        res = total(res, 4, nan = nan)
237      ENDIF ELSE BEGIN
238        if keyword_set(nan) then begin
239          divi = finite(res)
240          divi = total(temporary(divi), 4)
241          notanum = where(divi EQ 0)
242          res = total(res, 4, /nan)/(1 > divi)
243          if notanum[0] NE -1 then res[temporary(notanum)] = !values.f_nan
244        ENDIF ELSE res = total(res, 4)/(1.*taille[4])
245      ENDELSE
246    ENDELSE
247    if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
248    return,  moyenne(temporary(res), direc, BOXZOOM = boxzoom, NAN = nan, INTEGRATION = integration, NODOMDEF = nodomdef, WDEPTH = wdepth, _extra = ex)
249  ENDIF ELSE res = tab
250  IF jpt EQ 1 THEN BEGIN
251    if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
252    return, moyenne(reform(res, /over), direc, BOXZOOM = boxzoom, NAN = nan, INTEGRATION = integration, NODOMDEF = nodomdef, WDEPTH = wdepth, _extra = ex)
253  END
254;------------------------------------------------------------
255;------------------------------------------------------------
256; II) Case 2d arrays series (tab3d)
257;------------------------------------------------------------
258;------------------------------------------------------------
259  if (dim eq '3d') then begin
260;---------------------------------------------------------------
261;   II.1) verification of the coherence of the array's size to average
262; Verification of the coherence between the array's size and the domain defined by domdef
263; The input array must have either the total domain's size (jpi,jpj,jpt) or
264; this one of the reduced domain (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    ; If nan is not !values.f_nan
278; we put it at !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; Comment : WE HAVE TO BE CAREFUL ABOUT CASES WHERE THE DIMENSION TO
286; AVERAGE = 1, AND MAKE SURE THAT IT EXIST. THAT IS WHY WE USE
287; reform(...,nx,ny,...) WHICH CAN LOOK USELESS AT THE BEGINNING
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) Different types of average
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) Case 3d arrays series (tab4d)
355;------------------------------------------------------------
356  if (dim eq '4d') then begin
357;---------------------------------------------------------------
358; III.1) Verification of the coherence of the array to average size
359; Verification of the coherence between the array's size and the domain
360; defind by domdef
361; The input array must have either the total domain size (jpi,jpj,jpk,jpt)
362; or this one of the reduced domain (nx,ny,ny,jpt)
363;---------------------------------------------------------------
364    case 1 of
365      taille[1] eq jpi and taille[2] eq jpj and taille[3] eq jpk and taille[4] eq jpt: $
366        res = tab[firstx:lastx, firsty:lasty, firstz:lastz, *]
367      taille[1] eq jpi and taille[2] eq jpj and taille[3] eq nz and taille[4] eq jpt: $
368        res = tab[firstx:lastx, firsty:lasty, *, *]
369      taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq nz and taille[4] eq jpt:res = tab
370      taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq jpk and taille[4] eq jpt: $
371        res = tab[*, *, firstz:lastz, *]
372      else:BEGIN
373        if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
374        return, report('Probleme d''adequation entre les tailles du domaine nx*ny*nz*jpt ' $
375                       +strtrim(nx, 1)+'*'+strtrim(ny, 1)+'*'+strtrim(nz, 1)+'*' $
376                       +strtrim(jpt, 1)+' et du tableau '+strtrim(taille[1], 1)+'*' $
377                       +strtrim(taille[2], 1)+'*'+strtrim(taille[3], 1)+'*' $
378                       +strtrim(taille[4], 1))
379      END
380    endcase
381    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)
382    if keyword_set(nan) NE 0 then BEGIN
383      if nan NE 1 then BEGIN    ; if nan is not !values.f_nan
384; we put it at !values.f_nan
385        if abs(nan) LT 1e6 then notanumber = where(res EQ nan) $
386        ELSE notanumber = where(abs(res) GT abs(nan)/10.)
387        if notanumber[0] NE -1 then res[temporary(notanumber)] = !values.f_nan
388      ENDIF
389    ENDIF
390;---------------------------------------------------------------
391; Comment : WE HAVE TO BE CAREFUL ABOUT CASES WHERE THE DIMENSION TO
392; AVERAGE = 1, AND MAKE SURE THAT IT EXIST. THAT IS WHY WE USE
393; reform(...,nx,ny,...) WHICH CAN LOOK USELESS AT THE BEGINNING
394;---------------------------------------------------------------
395    if nx EQ 1 OR ny EQ 1 OR nz EQ 1 then BEGIN
396      res = reform(res, nx, ny, nz, jpt, /over)
397      mask =  reform(mask, nx, ny, nz, /over)
398    ENDIF
399    IF keyword_set(key_partialstep) THEN BEGIN
400; the top of the ocean floor is
401      IF vargrid EQ 'T' OR vargrid EQ 'W' THEN bottom = total(mask, 3) $
402      ELSE bottom = total(tmask[firstx:lastx, firsty:lasty, firstz:lastz], 3)
403; we suppress columns with only ocean or land
404      good = where(bottom NE 0 AND bottom NE nz)
405; the bottom of the ocean in 3D index is:
406      bottom = lindgen(nx*ny)+(temporary(bottom)-1L)*nx*ny
407      IF good[0] NE -1 THEN bottom = bottom[good] $
408      ELSE bottom = -1
409    ENDIF ELSE bottom = -1
410;---------------------------------------------------------------
411; III.2) different average types
412;---------------------------------------------------------------
413    IF keyword_set(nan) NE 0 THEN msknan = finite(res) ELSE msknan = -1
414    case 1 of
415      (dirx eq 1) and (diry eq 0) and (dirz eq 0) : BEGIN
416        e13 = (temporary(e1))[*]#replicate(1., nz)
417        e13 = reform(e13, nx, ny, nz, /over)
418        echelle = (temporary(e13)*temporary(mask))[*]#replicate(1, jpt)
419        echelle = reform(echelle, nx, ny, nz, jpt, /over)
420        IF keyword_set(key_partialstep) AND bottom[0] NE -1 $
421          AND nx NE 1 AND NOT keyword_set(keepbottom) THEN BEGIN
422          IF msknan[0] EQ -1 THEN BEGIN
423            msknan = replicate(1b, nx, ny, nz, jpt)
424            nan = 1
425          ENDIF
426          bottom = bottom#replicate(1, jpt) $ ; 4D bottom!
427            + replicate(1, n_elements(bottom))#(nx*ny*nz*lindgen(jpt))
428          msknan[bottom] = 0
429          res[temporary(bottom)] = !values.f_nan
430        ENDIF
431        if keyword_set(integration) then divi = 1 ELSE begin
432          IF msknan[0] NE -1 THEN divi = total(echelle*msknan, 1) $
433          ELSE divi = total(echelle, 1)
434        endelse
435        res = temporary(res)*echelle
436        res = total(temporary(res), 1, nan = nan)/(divi > 1)
437        if msknan[0] NE -1 then begin
438          echelle = temporary(echelle) NE 0
439          testnan = temporary(msknan)*echelle
440          testnan = total(temporary(testnan), 1) $
441            +(total(temporary(echelle), 1) EQ 0)
442        endif
443      end
444      (dirx eq 0) and (diry eq 1) and (dirz eq 0) : begin
445        e23 = temporary(e2[*])#replicate(1., nz)
446        e23 = reform(e23, nx, ny, nz, /over)
447        echelle = (temporary(e23)*temporary(mask))[*]#replicate(1, jpt)
448        echelle = reform(echelle, nx, ny, nz, jpt, /over)
449        IF keyword_set(key_partialstep) AND bottom[0] NE -1 $
450          AND ny NE 1 AND NOT keyword_set(keepbottom) THEN BEGIN
451          IF msknan[0] EQ -1 THEN BEGIN
452            msknan = replicate(1b, nx, ny, nz, jpt)
453            nan = 1
454          endif
455          bottom = bottom#replicate(1, jpt) $ ; 4D bottom!
456            + replicate(1, n_elements(bottom))#(nx*ny*nz*lindgen(jpt))
457          msknan[bottom] = 0
458          res[temporary(bottom)] = !values.f_nan
459        ENDIF
460        if keyword_set(integration) then divi = 1 ELSE begin
461          IF msknan[0] NE -1 THEN divi = total(echelle*msknan, 2) $
462          ELSE divi = total(echelle, 2)
463        endelse
464        res = total(temporary(res)*echelle, 2, nan = nan)/(divi > 1)
465        if msknan[0] NE -1 then begin
466          echelle = temporary(echelle) NE 0
467          testnan = temporary(msknan)*echelle
468          testnan = total(temporary(testnan), 2) $
469            +(total(temporary(echelle), 2) EQ 0)
470        endif
471      end
472      (dirx eq 0) and (diry eq 0) and (dirz eq 1) : begin
473        e33 = replicate(1, 1.*nx*ny)#e3
474        e33 = reform(e33, nx, ny, nz, /over)
475        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
476          IF keyword_set(wdepth) THEN $
477            e33[bottom] = (e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
478          ELSE e33[bottom] = (e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
479        ENDIF
480        echelle = (temporary(e33)*temporary(mask))[*]#replicate(1, jpt)
481        echelle = reform(echelle, nx, ny, nz, jpt, /over)
482        IF keyword_set(sshh) THEN echelle[*, *, 0, *] = echelle[*, *, 0, *] + sshh
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 AND NOT keyword_set(keepbottom) THEN BEGIN
504          IF msknan[0] EQ -1 THEN BEGIN
505            msknan = replicate(1b, nx, ny, nz, jpt)
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(sshh) THEN echelle[*, *, 0, *] = echelle[*, *, 0, *] + sshh*( e1[*]#replicate(1., jpt) )
535        if keyword_set(integration) then divi = 1 ELSE begin
536          IF msknan[0] NE -1 THEN divi = total(total(echelle*msknan, 1), 2) $
537          ELSE divi = total(total(echelle, 1), 2)
538        endelse
539        res = total(total(temporary(res)*echelle, 1, nan = nan), 2, nan = nan)/(divi > 1)
540        if msknan[0] NE -1 then begin
541          echelle = temporary(echelle) NE 0
542          testnan = temporary(msknan)*echelle
543          testnan = total(total(temporary(testnan), 1), 2) $
544            +(total(total(temporary(echelle), 1), 2) EQ 0)
545        endif
546      end
547      (dirx eq 0) and (diry eq 1) and (dirz eq 1) : begin
548        e233 = e2[*]#e3
549        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
550          IF keyword_set(wdepth) THEN $
551            e233[bottom] = (e2*e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
552          ELSE e233[bottom] = (e2*e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
553        ENDIF
554        echelle = (temporary(e233[*])*temporary(mask[*]))#replicate(1, jpt)
555        echelle = reform(echelle, nx, ny, nz, jpt, /over)
556        IF keyword_set(sshh) THEN echelle[*, *, 0, *] = echelle[*, *, 0, *] + sshh*( e2[*]#replicate(1., jpt) )
557        if keyword_set(integration) then divi = 1 ELSE begin
558          IF msknan[0] NE -1 THEN divi = total(total(echelle*msknan, 2), 2) $
559          ELSE divi = total(total(echelle, 2), 2)
560        endelse
561        res = total(total(temporary(res)*echelle, 2, nan = nan), 2, nan = nan)/(divi > 1)
562        if msknan[0] NE -1 then begin
563          echelle = temporary(echelle) NE 0
564          testnan = temporary(msknan)*echelle
565          testnan = total(total(temporary(testnan), 2), 2) $
566            +(total(total(temporary(echelle), 2), 2) EQ 0)
567        endif
568      end
569      (dirx eq 1) and (diry eq 1) and (dirz eq 1) : begin
570        e1233 = (e1[*]*e2[*])#e3
571        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
572          IF keyword_set(wdepth) THEN $
573            e1233[bottom] = (e1*e2*e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
574          ELSE e1233[bottom] = (e1*e2*e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
575        ENDIF
576        echelle = (temporary(e1233[*])*temporary(mask[*]))#replicate(1, jpt)
577        echelle = reform(echelle, nx, ny, nz, jpt, /over)
578        IF keyword_set(sshh) THEN echelle[*, *, 0, *] = echelle[*, *, 0, *] + sshh*( (e1[*]*e2[*])#replicate(1., jpt) )
579        if keyword_set(integration) then divi = 1 ELSE begin
580          IF msknan[0] NE -1 THEN divi = total(total(total(echelle*msknan, 1), 1), 1) $
581          ELSE divi = total(total(total(echelle, 1), 1), 1)
582        endelse
583        res = total(total(total(temporary(res)*echelle, 1, nan = nan), 1, nan = nan), 1, nan = nan)/(divi > 1)
584        if msknan[0] NE -1 then begin
585          echelle = temporary(echelle) NE 0
586          testnan = temporary(msknan)*echelle
587          testnan = total(total(total(temporary(testnan), 1), 1), 1) $
588            +(total(total(total(temporary(echelle), 1), 1), 1) EQ 0)
589        endif
590      end
591    endcase
592  endif
593;------------------------------------------------------------
594  if dirt EQ 1 AND keyword_set(spatialfirst) then BEGIN
595    IF (reverse(size(res, /dimension)))[0] NE jpt THEN BEGIN
596      ras = report('the last dimension of res is not equal to jpt: '+strtrim(jpt, 2))
597      if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
598      return, -1
599    ENDIF
600    tdim = size(res, /n_dimensions)
601    if keyword_set(integration) then res = total(res, tdim, nan = nan) $
602    ELSE BEGIN
603      if keyword_set(nan) then BEGIN
604        testnan = testnan < 1
605        testnan = total(temporary(testnan), tdim)
606        divi = testnan
607      ENDIF ELSE divi = jpt
608      res = total(res, tdim, nan = nan)/(1 > divi)
609    ENDELSE
610  ENDIF
611;------------------------------------------------------------
612;------------------------------------------------------------
613;IV ) finishing
614;------------------------------------------------------------
615;------------------------------------------------------------
616; IV.1) We mask land by a value equal to 1.e+20
617;------------------------------------------------------------
618  valmask = 1e+20
619  terre = where(divi EQ 0)
620  IF terre[0] NE -1 THEN BEGIN
621    res[temporary(terre)] = 1e+20
622  ENDIF
623;------------------------------------------------------------
624; IV.2) We replace, when nan equal 1, !values.f_nan by nan
625;------------------------------------------------------------
626  if keyword_set(nan) NE 0 then BEGIN
627    puttonan = where(temporary(testnan) EQ 0)
628    if puttonan[0] NE -1 then res[temporary(puttonan)] = !values.f_nan
629    if nan NE 1 then BEGIN
630      notanumber = where(finite(res) eq 0)
631      if notanumber[0] NE -1 then res[temporary(notanumber)] = nan
632    ENDIF
633  ENDIF
634;------------------------------------------------------------
635; IV.3) We replace in the domain whch was defined at the entry of average
636;------------------------------------------------------------
637  if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4grmoyenne.dat'
638;------------------------------------------------------------
639  if keyword_set(key_performance) THEN print, 'temps grossemoyenne', systime(1)-tempsun
640  return, res
641;------------------------------------------------------------
642;------------------------------------------------------------
643end
Note: See TracBrowser for help on using the repository browser.