source: trunk/SRC/ToBeReviewed/CALCULS/moyenne.pro @ 370

Last change on this file since 370 was 370, checked in by pinsard, 16 years ago

improvemnts of headers (typo, links)

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 23.3 KB
RevLine 
[2]1;+
2;
[223]3; @file_comments
[142]4; averages a 2- or 3-d field over a selected
[268]5;           geographical area and along one or more
[2]6;           selected axes (x, y or z)
7;
[142]8; @categories
[2]9;
[163]10; @param TAB {in}{required}
[142]11; 2 or 3d field
[2]12;
[142]13; @param DIREC {in}{required}
14; 'x' 'y' 'z' 'xy' 'xz' 'yz' or 'xyz'
[2]15;
[223]16; @keyword BOXZOOM
[254]17; [xmin,xmax,ymin,ymax (,(zmin,)zmax)] to more details, see <pro>domdef</pro>
[223]18; boxzoom can have 5 forms:
[163]19;  [vert2],
20;  [vert1, vert2],
[223]21;  [lon1, lon2, lat1, lat2],
[163]22;  [lon1, lon2, lat1, lat2, vert2],
23;  [lon1, lon2, lat1, lat2, vert1,vert2]
[2]24;
[223]25; @keyword NAN
[142]26; not a number, we activate it if we want to average without considerate some masked values of TAB.
[163]27; If masked values of TAB are values consecrated by IDL(!values.f_nan), we just have to put NAN.
[142]28; If masked values of TAB are valued a (a must be different of 1, corresponding to nan =
[223]29; !values.f_nan and of 0, which desactivate nan). We have to put NAN=a.
[163]30; Comment: In output, result points which are NAN will be valued a or !values.f_nan.
[223]31;
[142]32; @keyword NODOMDEF
[237]33; We activate it if we do not want to pass in <pro>domdef</pro> even if the
34; keyword boxzoom is present (like when <pro>grossemoyenne</pro> is called
35; via <pro>checkfield</pro>)
[2]36;
[223]37; @keyword INTEGRATION
[142]38; To make an integral rather than an average
[223]39;
40; @keyword WDEPTH
41; to specify that the field is at W depth instead of T
42; depth (automatically activated if vargrid eq 'W')
43;
[142]44; @returns
[223]45; An array
[2]46;
[142]47; @uses
[370]48; <pro>common</pro>
[254]49; <pro>domdef</pro>
[2]50;
[223]51; @restrictions
52; Put values corresponding to land at 1.e20
[2]53;
[142]54; @history
[157]55;  Jerome Vialard (jv\@lodyc.jussieu.fr)
[2]56;                       2/7/98
[157]57;                       Sebastien Masson (smasson\@lodyc.jussieu.fr)
[2]58;                       14/8/98
59;                       15/1/98
[142]60;                       11/3/99 adaptation for NAN
61;                       28/7/99 Averages 1d arrays
62;
63; @version
64; $Id$
65;
[2]66;-
[327]67FUNCTION moyenne, tab, direc, BOXZOOM=boxzoom, INTEGRATION=integration $
68                , NAN=nan, NODOMDEF=nodomdef, WDEPTH=wdepth $
69                , _EXTRA=ex
[114]70;
71  compile_opt idl2, strictarrsubs
72;
[25]73@cm_4mesh
74@cm_4data
75@cm_4cal
76  IF NOT keyword_set(key_forgetold) THEN BEGIN
77@updatenew
78@updatekwd
79  ENDIF
80;---------------------------------------------------------
[142]81  tempsun = systime(1)          ; To key_performance
[2]82;------------------------------------------------------------
[142]83;I) preliminaries
[2]84;------------------------------------------------------------
[25]85  dirt = 0
86  dirx = 0
87  diry = 0
88  dirz = 0
[2]89;------------------------------------------------------------
[142]90; I.1) Directions(s) we follow to integrate
[2]91;------------------------------------------------------------
[25]92  if ( strpos(direc, 't') ge 0 ) then dirt = 1
93  if ( strpos(direc, 'x') ge 0 ) then dirx = 1
94  if ( strpos(direc, 'y') ge 0 ) then diry = 1
95  if ( strpos(direc, 'z') ge 0 ) then dirz = 1
96  if (dirx eq 0 and diry eq 0 and dirz eq 0) then return, tab
[2]97;------------------------------------------------------------
[142]98; I.2) verification of the input array's size
[2]99;------------------------------------------------------------
[25]100  taille = size(tab)
101  case 1 of
102    taille[0] eq 1 :dim = '1d'
103    taille[0] eq 2 :BEGIN
104      dim = '2d'
105      if dirx eq 0 and diry eq 0 then return, tab
106    END
107    taille[0] eq 3 :BEGIN
108      dim = '3d'
109      if dirx eq 0 and diry eq 0 and dirz eq 0 then return, tab
110    END
[223]111    else : return, report('Array must have 2 or 3 dimensions if there is a time dimension use grossemoyenne')
[25]112  endcase
[2]113;------------------------------------------------------------
[142]114;   I.3) Obtainment of scale's factors and of the mask on the subdomain concernedby the average.
115; Redefinition of the domain ajusted at boxzoom (at 6 elements)
116; This will allowed us to calculate only in the domain concerned by the average.
[223]117; Domdef, followed by grid give us all arrays of the grid on the subdomain
[2]118;------------------------------------------------------------
[223]119  if keyword_set(boxzoom) then BEGIN
[25]120    Case 1 Of
121      N_Elements(Boxzoom) Eq 1:bte = [lon1, lon2, lat1, lat2, 0., boxzoom[0]]
122      N_Elements(Boxzoom) Eq 2:bte = [lon1, lon2, lat1, lat2, boxzoom[0], boxzoom[1]]
123      N_Elements(Boxzoom) Eq 4:bte = [Boxzoom, vert1, vert2]
124      N_Elements(Boxzoom) Eq 5:bte = [Boxzoom[0:3], 0, Boxzoom[4]]
125      N_Elements(Boxzoom) Eq 6:bte = Boxzoom
[223]126      Else: return, report('Bad definition of Boxzoom')
[25]127    endcase
[223]128    if NOT keyword_set(nodomdef) then BEGIN
[25]129      savedbox = 1b
130      saveboxparam, 'boxparam4moyenne.dat'
131      domdef, bte, GRIDTYPE = vargrid, _extra = ex
[223]132    ENDIF
133  ENDIF
[2]134;---------------------------------------------------------------
[142]135; attribution of the mask and of longitude and latitude arrays...
[2]136;---------------------------------------------------------------
[25]137  IF vargrid EQ 'W' THEN wdepth = 1
138  grille, mask, glam, gphi, gdep, nx, ny, nz, firstx, firsty, firstz, lastx, lasty, lastz, e1, e2, e3, WDEPTH = wdepth
[2]139;------------------------------------------------------------
140;------------------------------------------------------------
[142]141; II) Case of the 1d array
[2]142;------------------------------------------------------------
143;------------------------------------------------------------
[25]144  if dim EQ '1d' then BEGIN
145    if n_elements(tab) NE nx*ny AND n_elements(tab) NE nx*ny*nz then BEGIN
146      if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
147      return, report('Probleme d''adequation entre les tailles du domaine et de la boxzoom.')
148    ENDIF
149    case 1 of
[142]150      nx EQ 1 AND ny EQ 1:BEGIN ;vector following z
[25]151        case n_elements(tab) of
152          jpk:res = tab[firstz:lastz]
153          nz:res = tab
[223]154          ELSE:BEGIN
[25]155            if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
156            return, report('Probleme d''adequation entre les tailles du domaine et de la boxzoom.')
157          END
158        ENDCASE
[223]159        if dirz EQ 1 then BEGIN
160          dim = '3d'
[25]161          taille = size(reform(res, nx, ny, nz))
162        ENDIF ELSE BEGIN
163          if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
164          return, res
[223]165        ENDELSE
[25]166      END
[142]167      ny EQ 1:BEGIN             ;vector following x
[25]168        case n_elements(tab) of
169          jpi:res = tab[firstx:lastx]
170          nx:res = tab
[223]171          ELSE:BEGIN
[25]172            if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
173            return, report('Probleme d''adequation entre les tailles du domaine et de la boxzoom.')
174          END
175        ENDCASE
[223]176        if dirx EQ 1 then BEGIN
177          dim = '2d'
[25]178          taille = size(reform(res, nx, ny))
[223]179        ENDIF ELSE BEGIN
[25]180          if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
181          return, res
182        ENDELSE
183      END
[142]184      nx EQ 1:BEGIN             ;vector following y
[25]185        case n_elements(tab) of
186          jpj:res = tab[firsty:lasty]
187          ny:res = tab
[223]188          ELSE:BEGIN
[25]189            if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
190            return, report('Probleme d''adequation entre les tailles du domaine et de la boxzoom.')
191          END
192        ENDCASE
193        if diry EQ 1 then BEGIN
194          dim = '2d'
195          taille = size(reform(res, nx, ny))
[223]196        ENDIF ELSE BEGIN
[25]197          if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
198          return, res
[223]199        ENDELSE
[25]200      END
201    endcase
202  endif
[2]203;------------------------------------------------------------
204;------------------------------------------------------------
[142]205; II) Case of the 2d array
[2]206;------------------------------------------------------------
207;------------------------------------------------------------
[25]208  if (dim eq '2d') then begin
[2]209;---------------------------------------------------------------
[142]210;   II.1) verification of the coherence of the array's size to average
211; Verification of the coherence between the array's size and the domain defined by domdef
[223]212; The input array must have either the total domain's size (jpi,jpj) or this
[142]213; one of the reduced domain (nx,ny)
[2]214;---------------------------------------------------------------
[25]215    case 1 of
216      taille[1] eq jpi and taille[2] eq jpj: $
217        res = tab[firstx:lastx, firsty:lasty]
218      taille[1] eq  nx and taille[2] eq  ny:res = tab
[223]219      else:BEGIN
[25]220        if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
221        return, report('Probleme d''adequation entre les tailles du domaine nx*ny '+strtrim(nx, 1)+'*'+strtrim(ny, 1)+' et du tableau '+strtrim(taille[1], 1)+'*'+strtrim(taille[2], 1))
222      END
223    ENDCASE
[223]224    if keyword_set(nan) NE 0 then BEGIN
225      if nan NE 1 then BEGIN    ; If nan is not !values.f_nan
[142]226; we put it at !values.f_nan
[25]227        if abs(nan) LT 1e6 then notanumber = where(res EQ nan) $
228        ELSE notanumber = where(abs(res) GT abs(nan)/10.)
229        if notanumber[0] NE -1 then res[temporary(notanumber)] = !values.f_nan
[2]230      ENDIF
[25]231    ENDIF
[2]232;---------------------------------------------------------------
[223]233; Comment : WE HAVE TO BE CAREFUL ABOUT CASES WHERE THE DIMENSION TO AVERAGE = 1,
234; AND MAKE SURE THAT IT EXIST. THAT IS WHY WE USE reform(...,nx,ny,...) WHICH CAN
[142]235; LOOK USELESS AT THE BEGINNING
[2]236;---------------------------------------------------------------
[223]237    if nx EQ 1 OR ny EQ 1 then BEGIN
[25]238      res = reform(res, nx, ny, /over)
239      e1 =  reform(e1, nx, ny, /over)
240      e2 =  reform(e2, nx, ny, /over)
241    endif
242    if nx EQ 1 OR ny EQ 1 OR nz EQ 1 THEN $
243      mask =  reform(mask, nx, ny, nz, /over)
[2]244;---------------------------------------------------------------
[142]245; II.3) Different types of average
[2]246;---------------------------------------------------------------
[25]247    mask = mask[*, *, 0]
248    if keyword_set(nan) NE 0 then msknan = finite(res) ELSE msknan = -1
249    case 1 of
250      (dirx eq 1) and (diry eq 0) : begin
251        e = e1*mask
252        if keyword_set(integration) then divi = 1 $
[223]253        else begin
[25]254          divi = e
255          IF msknan[0] NE -1 THEN divi = temporary(divi)*msknan
256          if ny EQ 1 then divi = reform(divi, nx, ny, /over)
257          divi = total(divi, 1)
258        endelse
259        res = res*e
260        if ny EQ 1 then res = reform(res, nx, ny, /over)
261        res = total(res, 1, nan = nan)/(divi > 1.)
262        if msknan[0] NE -1 then begin
263          testnan  = msknan*mask
264          if ny EQ 1 then testnan = reform(testnan, nx, ny, /over)
265          testnan = total(testnan, 1)+(total(mask, 1) EQ 0)
266        endif
267      end
268      (dirx eq 0) and (diry eq 1) : begin
269        e = e2*mask
270        if keyword_set(integration) then divi = 1 $
[223]271        else begin
[25]272          divi = e
273          IF msknan[0] NE -1 THEN divi = temporary(divi)*msknan
274          if ny EQ 1 then divi = reform(divi, nx, ny, /over)
275          divi = total(divi, 2)
276        endelse
277        res = res*e
278        if ny EQ 1 then res = reform(res, nx, ny, /over)
279        res = total(res, 2, nan = nan)/(divi > 1.)
280        if msknan[0] NE -1 then begin
281          testnan  = msknan*mask
282          if ny EQ 1 then testnan  = reform(testnan, nx, ny, /over)
283          testnan = total(testnan, 2)+(total(mask, 2) EQ 0)
284        endif
285      end
286      (dirx eq 1) and (diry eq 1) : begin
[223]287        if keyword_set(integration) then divi = 1 else BEGIN
[25]288          IF msknan[0] NE -1 THEN divi = total(e1*e2*mask*msknan) $
289          ELSE divi = total(e1*e2*mask)
[223]290        ENDELSE
[25]291        res = total(res*e1*e2*mask, nan = nan)/(divi > 1.)
292        if msknan[0] NE -1 then begin
293          testnan  = msknan*mask
294          testnan = total(testnan)+(total(mask) EQ 0)
295        endif
296      end
297    endcase
298  endif
[2]299;------------------------------------------------------------
300;------------------------------------------------------------
[142]301; III) Case 3d arrays series (tab4d)
[2]302;------------------------------------------------------------
303;------------------------------------------------------------
[25]304  if (dim eq '3d') then begin
[2]305;---------------------------------------------------------------
[223]306; III.1) Verification of the coherence of the array to average size
307; Verification of the coherence between the array's size and the domain
308; defind by domdef
309; The input array must have either the total domain size (jpi,jpj,jpk)
[142]310; or this one of the reduced domain (nx,ny,ny)
[2]311;---------------------------------------------------------------
[25]312    case 1 of
313      taille[1] eq jpi and taille[2] eq jpj and taille[3] eq jpk: $
314        res = tab[firstx:lastx, firsty:lasty, firstz:lastz]
315      taille[1] eq jpi and taille[2] eq jpj and taille[3] eq nz: $
316        res = tab[firstx:lastx, firsty:lasty, *]
317      taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq nz :res = tab
318      taille[1] EQ  nx and taille[2] eq  ny and taille[3] eq jpk : $
319        res = tab[*, *, firstz:lastz]
[223]320      else:BEGIN
[25]321        if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
322        return, report('Probleme d''adequation entre les tailles du domaine nx*ny*nz '+strtrim(nx, 1)+'*'+strtrim(ny, 1)+'*'+strtrim(nz, 1)+' et du tableau '+strtrim(taille[1], 1)+'*'+strtrim(taille[2], 1)+'*'+strtrim(taille[3], 1))
323      END
324    endcase
[223]325    if keyword_set(nan) NE 0 then BEGIN
326      if nan NE 1 then BEGIN    ; if nan is not !values.f_nan
[142]327; we put it at !values.f_nan
[25]328        if abs(nan) LT 1e6 then notanumber = where(res EQ nan) $
329        ELSE notanumber = where(abs(res) GT abs(nan)/10.)
330        if notanumber[0] NE -1 then res[temporary(notanumber)] = !values.f_nan
[2]331      ENDIF
[25]332    ENDIF
[2]333;---------------------------------------------------------------
[223]334; Comment : WE HAVE TO BE CAREFUL ABOUT CASES WHERE THE DIMENSION TO AVERAGE = 1,
335; AND MAKE SURE THAT IT EXIST. THAT IS WHY WE USE reform(...,nx,ny,...) WHICH CAN
[142]336; LOOK USELESS AT THE BEGINNING
[2]337;---------------------------------------------------------------
[223]338    if nx EQ 1 OR ny EQ 1 OR nz EQ 1 then BEGIN
[25]339      res = reform(res, nx, ny, nz, /over)
340      e1 =  reform(e1, nx, ny, /over)
341      e2 =  reform(e2, nx, ny, /over)
342    endif
343    if nx EQ 1 OR ny EQ 1 OR nz EQ 1 THEN $
344      mask =  reform(mask, nx, ny, nz, /over)
345    IF keyword_set(key_partialstep) THEN BEGIN
346; the top of the ocean floor is
347      IF vargrid EQ 'T' OR vargrid EQ 'W' THEN bottom = total(mask, 3) $
[223]348      ELSE bottom = total(tmask[firstx:lastx, firsty:lasty, firstz:lastz], 3)
349; we suppress columns with only ocean or land
[25]350      good = where(bottom NE 0 AND bottom NE nz)
351; the bottom of the ocean in 3D index is:
352      bottom = lindgen(nx*ny)+(temporary(bottom)-1L)*nx*ny
353      IF good[0] NE -1 THEN bottom = bottom[good] $
354      ELSE bottom = -1
355    ENDIF ELSE bottom = -1
[2]356;---------------------------------------------------------------
[142]357; III.2) different average types
[2]358;---------------------------------------------------------------
[25]359    if keyword_set(nan) NE 0 then msknan = finite(res) ELSE msknan = -1
360    case 1 of
361      (dirx eq 1) and (diry eq 0) and (dirz eq 0) : begin
362        e13 = e1[*]#replicate(1., nz)
363        e13 = reform(e13, nx, ny, nz, /over)
364        IF keyword_set(key_partialstep) AND bottom[0] NE -1 $
365          AND nx NE 1 THEN BEGIN
[223]366          IF msknan[0] EQ -1 THEN BEGIN
[25]367            msknan = replicate(1b, nx, ny, nz)
368            nan = 1
369          endif
370          msknan[bottom] = 0
371          res[bottom] = !values.f_nan
372        ENDIF
373        if keyword_set(integration) then divi = 1 else begin
374          divi = e13*mask
375          IF msknan[0] NE -1 THEN divi = temporary(divi)*msknan
376          if nz EQ 1 then divi = reform(divi, nx, ny, nz, /over)
377          divi = total(divi, 1)
378        ENDELSE
379        res = res*e13*mask
380        if nz EQ 1 then res = reform(res, nx, ny, nz, /over)
381        res = total(res, 1, nan = nan)/(divi > 1.)
382        e13 = 1
383        if msknan[0] NE -1 then begin
384          testnan  = msknan*mask
385          if nz EQ 1 then testnan  = reform(testnan, nx, ny, nz, /over)
386          testnan = total(testnan, 1)+(total(mask, 1) EQ 0)
387        endif
388      end
389      (dirx eq 0) and (diry eq 1) and (dirz eq 0) : begin
390        e23 = e2[*]#replicate(1., nz)
391        e23 = reform(e23, nx, ny, nz, /over)
392        IF keyword_set(key_partialstep) AND bottom[0] NE -1 $
393          AND ny NE 1 THEN BEGIN
[223]394          IF msknan[0] EQ -1 THEN BEGIN
[25]395            msknan = replicate(1b, nx, ny, nz)
396            nan = 1
397          endif
398          msknan[bottom] = 0
399          res[bottom] = !values.f_nan
400        ENDIF
401        if keyword_set(integration) then divi = 1 else begin
402          divi = e23*mask
403          IF msknan[0] NE -1 THEN divi = temporary(divi)*msknan
404          if nz EQ 1 then divi = reform(divi, nx, ny, nz, /over)
405          divi = total(divi, 2)
406        ENDELSE
407        res = res*e23*mask
408        if nz EQ 1 then res = reform(res, nx, ny, nz, /over)
409        res = total(res, 2, nan = nan)/(divi > 1.)
410        e23 = 1
411        if msknan[0] NE -1 then begin
412          testnan  = msknan*mask
413          if nz EQ 1 then testnan = reform(testnan, nx, ny, nz, /over)
414          testnan = total(testnan, 2)+(total(mask, 2) EQ 0)
415        endif
416      end
417      (dirx eq 0) and (diry eq 0) and (dirz eq 1) : begin
418        e33 = replicate(1, 1.*nx*ny)#e3
419        e33 = reform(e33, nx, ny, nz, /over)
420        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
421          IF keyword_set(wdepth) THEN $
422            e33[bottom] = (e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
423          ELSE e33[bottom] = (e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
424        ENDIF
425        if keyword_set(integration) then divi = 1 else begin
426          divi = e33*mask
427          if msknan[0] NE -1 then divi = temporary(divi)*msknan
428          if nz EQ 1 then divi = reform(divi, nx, ny, nz, /over)
429          divi = total(divi, 3)
430        ENDELSE
431        res = res*e33*mask
432        if nz EQ 1 then res = reform(res, nx, ny, nz, /over)
433        res = total(res, 3, nan = nan)/(divi > 1.)
434        e33 = 1
435        if msknan[0] NE -1 then begin
436          testnan  = msknan*mask
437          if nz EQ 1 then testnan  = reform(testnan, nx, ny, nz, /over)
438          testnan = total(testnan, 3)+(total(mask, 3) EQ 0)
439        endif
440      end
441      (dirx eq 1) and (diry eq 1) and (dirz eq 0) : begin
442        e123 = (e1*e2)[*]#replicate(1., nz)
443        e123 = reform(e123, nx, ny, nz, /over)
444        IF keyword_set(key_partialstep) AND bottom[0] NE -1 $
445          AND nx*ny NE 1 THEN BEGIN
[223]446          IF msknan[0] EQ -1 THEN BEGIN
[25]447            msknan = replicate(1b, nx, ny, nz)
448            nan = 1
449          endif
450          msknan[bottom] = 0
451          res[bottom] = !values.f_nan
452        ENDIF
[223]453        if keyword_set(integration) then divi = 1 else BEGIN
[25]454          divi = e123*mask
455          IF msknan[0] NE -1 THEN divi = temporary(divi)*msknan
456          if nz EQ 1 then divi = reform(divi, nx, ny, nz, /over)
457          divi = total(total(divi, 1), 1)
458        ENDELSE
459        res = res*e123*mask
460        if nz EQ 1 then res = reform(res, nx, ny, nz, /over)
461        res = total(total(res, 1, nan = nan), 1, nan = nan) / (divi > 1.)
462        e123 = 1
463        if msknan[0] NE -1 then begin
464          testnan  = msknan*mask
465          if nz EQ 1 then testnan  = reform(testnan, nx, ny, nz, /over)
466          testnan = total(total(testnan, 1), 1)+(total(total(mask, 1), 1) EQ 0)
467        endif
468      end
469      (dirx eq 1) and (diry eq 0) and (dirz eq 1) : begin
470        e133 = e1[*]#e3
471        e133 = reform(e133, nx, ny, nz, /over)
472        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
473          IF keyword_set(wdepth) THEN $
474            e133[bottom] = (e1*e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
475          ELSE e133[bottom] = (e1*e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
476        ENDIF
[223]477        if keyword_set(integration) then divi = 1 else BEGIN
[25]478          divi = e133*mask
479          if msknan[0] NE -1 then divi = temporary(divi)*msknan
480          if nz EQ 1 then divi = reform(divi, nx, ny, nz, /over)
481          divi = total(total(divi, 1), 2)
482        ENDELSE
483        res = res*e133*mask
484        if nz EQ 1 then res = reform(res, nx, ny, nz, /over)
485        res = total(total(res, 1, nan = nan), 2, nan = nan) / (divi > 1.)
486        e133 = 1
487        if msknan[0] NE -1 then begin
488          testnan  = msknan*mask
489          if nz EQ 1 then testnan  = reform(testnan, nx, ny, nz, /over)
490          testnan = total(total(testnan, 1), 2)+(total(total(mask, 1), 2) EQ 0)
491        endif
492      end
493      (dirx eq 0) and (diry eq 1) and (dirz eq 1) : begin
494        e233 = e2[*]#e3
495        e233 = reform(e233, nx, ny, nz, /over)
496        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
497          IF keyword_set(wdepth) THEN $
498            e233[bottom] = (e2*e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
499          ELSE e233[bottom] = (e2*e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
500        ENDIF
[223]501        if keyword_set(integration) then divi = 1 else BEGIN
[25]502          divi = e233*mask
503          if msknan[0] NE -1 then divi = temporary(divi)*msknan
504          if nz EQ 1 then divi = reform(divi, nx, ny, nz, /over)
505          divi = total(total(divi, 2), 2)
506        ENDELSE
507        res = res*e233*mask
508        if nz EQ 1 then res = reform(res, nx, ny, nz, /over)
509        res = total(total(res, 2, nan = nan), 2, nan = nan) / (divi > 1.)
510        e233 = 1
511        if msknan[0] NE -1 then begin
512          testnan  = msknan*mask
513          if nz EQ 1 then testnan  = reform(testnan, nx, ny, nz, /over)
514          testnan = total(total(testnan, 2), 2)+(total(total(mask, 2), 2) EQ 0)
515        endif
516      end
517      (dirx eq 1) and (diry eq 1) and (dirz eq 1) : begin
518        e1233 = (e1*e2)[*]#e3
519        e1233 = reform(e1233, nx, ny, nz, /over)
520        IF keyword_set(key_partialstep) AND bottom[0] NE -1 THEN BEGIN
521          IF keyword_set(wdepth) THEN $
522            e1233[bottom] = (e1*e2*e3w_ps[firstx:lastx, firsty:lasty])[temporary(good)] $
523          ELSE e1233[bottom] = (e1*e2*e3t_ps[firstx:lastx, firsty:lasty])[temporary(good)]
524        ENDIF
[223]525        if keyword_set(integration) then divi = 1 else BEGIN
[25]526          if msknan[0] NE -1 then divi = total(e1233*mask*msknan) $
527          ELSE divi = total(e1233*mask)
528        ENDELSE
529        res = total(res*e1233*mask, nan = nan) / (divi > 1.)
530        e1233 = 1
531        if msknan[0] NE -1 then begin
532          testnan  = msknan*mask
533          testnan = total(testnan)+(total(mask) EQ 0)
534        endif
535      end
536    endcase
537  endif
[2]538;------------------------------------------------------------
539;------------------------------------------------------------
[142]540;IV ) finishing
[2]541;------------------------------------------------------------
542;------------------------------------------------------------
[142]543; IV.1) We mask land by a value equal to 1.e+20
[2]544;------------------------------------------------------------
[25]545  valmask = 1e+20
546  terre = where(divi EQ 0)
547  IF terre[0] NE -1 THEN BEGIN
[114]548    res[terre] = 1e+20
[223]549  ENDIF
[2]550;------------------------------------------------------------
[142]551; IV.2) We replace, when nan equal 1, !values.f_nan by nan
[2]552;------------------------------------------------------------
[223]553  if keyword_set(nan) NE 0 then BEGIN
[25]554    puttonan = where(testnan EQ 0)
555    if puttonan[0] NE -1 then res[puttonan] = !values.f_nan
[223]556    if nan NE 1 then BEGIN
[25]557      notanumber = where(finite(res) eq 0)
558      if notanumber[0] NE -1 then res[notanumber] = nan
559    ENDIF
560  ENDIF
[2]561;------------------------------------------------------------
[142]562; IV.3) We replace in the domain whch was defined at the entry of average
[2]563;------------------------------------------------------------
[25]564  if keyword_set(savedbox) THEN restoreboxparam, 'boxparam4moyenne.dat'
[2]565;------------------------------------------------------------
[223]566  if keyword_set(key_performance) THEN print, 'temps moyenne', systime(1)-tempsun
[25]567  return, res
[2]568;------------------------------------------------------------
569;------------------------------------------------------------
570end
Note: See TracBrowser for help on using the repository browser.