LMDZ
convmas_loc.F90
Go to the documentation of this file.
1 SUBROUTINE convmas_loc (pbaru, pbarv, convm)
2 !
3 !-------------------------------------------------------------------------------
4 ! Authors: P. Le Van , Fr. Hourdin.
5 !-------------------------------------------------------------------------------
6 ! Purpose: Compute mass flux convergence at p levels.
7  USE parallel_lmdz
8  USE mod_filtreg_p
9  IMPLICIT NONE
10  include "dimensions.h"
11  include "paramet.h"
12  include "comgeom.h"
13  include "logic.h"
14 !===============================================================================
15 ! Arguments:
16  REAL, INTENT(IN) :: pbaru(ijb_u:ije_u,llm)
17  REAL, INTENT(IN) :: pbarv(ijb_v:ije_v,llm)
18  REAL, INTENT(OUT) :: convm(ijb_u:ije_u,llm)
19 !===============================================================================
20 ! Method used: Computation from top to bottom.
21 ! Mass convergence at level llm is equal to zero and is not stored in convm.
22 !===============================================================================
23 ! Local variables:
24  INTEGER :: l, ijb, ije, jjb, jje
25 !===============================================================================
26 
27 !--- Computation of - (d(pbaru)/dx + d(pbarv)/dy )
28  CALL convflu_loc( pbaru, pbarv, llm, convm )
29 
30 !--- Filter
31  jjb=jj_begin
32  jje=jj_end+1
33  IF(pole_sud) jje=jj_end
34  CALL filtreg_p(convm,jjb_u,jje_u,jjb,jje,jjp1,llm,2,2,.true.,1)
35 
36 !--- Mass convergence is integrated from top to bottom
37 !$OMP BARRIER
38 !$OMP MASTER
39  ijb=ij_begin
40  ije=ij_end+iip1
41  IF(pole_sud) ije=ij_end
42  DO l=llmm1,1,-1
43  convm(ijb:ije,l) = convm(ijb:ije,l) + convm(ijb:ije,l+1)
44  END DO
45 !$OMP END MASTER
46 !$OMP BARRIER
47 
48 END SUBROUTINE convmas_loc
49 
integer, save jjb_u
subroutine filtreg_p(champ, ibeg, iend, nlat, nbniv, ifiltre, iaire, griscal, iter)
Definition: filtreg_p.F:5
integer, save jj_end
subroutine convmas_loc(pbaru, pbarv, convm)
Definition: convmas_loc.F90:2
integer, save jj_begin
integer, save ij_end
logical, save pole_sud
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
integer, save ijb_v
!$Header jjp1
Definition: paramet.h:14
integer, save jje_u
subroutine convflu_loc(xflu, yflu, nbniv, convfl)
Definition: convflu_loc.F:2
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
integer, save ij_begin
integer, save ije_v
integer, save ije_u
integer, save ijb_u