LMDZ
tourpot_loc.F90
Go to the documentation of this file.
1 SUBROUTINE tourpot_loc ( vcov, ucov, massebxy, vorpot )
2 !
3 !-------------------------------------------------------------------------------
4 ! Authors: P. Le Van.
5 !-------------------------------------------------------------------------------
6 ! Purpose: Compute potential vorticity.
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) :: vcov (ijb_v:ije_v,llm)
17  REAL, INTENT(IN) :: ucov (ijb_u:ije_u,llm)
18  REAL, INTENT(IN) :: massebxy(ijb_v:ije_v,llm)
19  REAL, INTENT(OUT) :: vorpot (ijb_v:ije_v,llm)
20 !===============================================================================
21 ! Method used:
22 ! vorpot = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) /psbarxy
23 !===============================================================================
24 ! Local variables:
25  INTEGER :: l, ij, ije, ijb, jje, jjb
26  REAL :: rot(ijb_v:ije_v,llm)
27 !===============================================================================
28 
29  ijb=ij_begin-iip1
30  ije=ij_end
31  IF(pole_nord) ijb=ij_begin
32 
33 !--- Wind vorticity ; correction: rot(iip1,j,l) = rot(1,j,l)
34 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
35  DO l=1,llm
36  IF(pole_sud) ije=ij_end-iip1-1
37  DO ij=ijb,ije
38  rot(ij,l)=vcov(ij+1,l)-vcov(ij,l)+ucov(ij+iip1,l)-ucov(ij,l)
39  END DO
40  IF(pole_sud) ije=ij_end-iip1
41  DO ij=ijb+iip1-1,ije,iip1; rot(ij,l)=rot(ij-iim,l); END DO
42  END DO
43 !$OMP END DO NOWAIT
44 
45 !--- Filter
46  jjb=jj_begin-1
47  jje=jj_end
48  IF(pole_nord) jjb=jjb+1
49  IF(pole_sud) jje=jje-1
50  CALL filtreg_p(rot,jjb_v,jje_v,jjb,jje,jjm,llm,2,1,.false.,1)
51 
52 !--- Potential vorticity ; correction: rot(iip1,j,l) = rot(1,j,l)
53 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
54  DO l=1,llm
55  IF(pole_sud) ije=ij_end-iip1-1
56  DO ij=ijb,ije
57  vorpot(ij,l)=(rot(ij,l)+fext(ij))/massebxy(ij,l)
58  END DO
59  IF(pole_sud) ije=ij_end-iip1
60  DO ij=ijb+iip1-1,ije,iip1; vorpot(ij,l)=vorpot(ij-iim,l); END DO
61  END DO
62 !$OMP END DO NOWAIT
63 
64 END SUBROUTINE tourpot_loc
65 
!$Header!CDK comgeom COMMON comgeom && fext
Definition: comgeom.h:25
integer, save jjb_v
subroutine filtreg_p(champ, ibeg, iend, nlat, nbniv, ifiltre, iaire, griscal, iter)
Definition: filtreg_p.F:5
integer, save jj_end
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
subroutine tourpot_loc(vcov, ucov, massebxy, vorpot)
Definition: tourpot_loc.F90:2
integer, save ijb_v
!$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 false
Definition: calcul_STDlev.h:26
logical, save pole_nord
integer, save ij_begin
integer, save ije_v
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
integer, save ije_u
integer, save jje_v
integer, save ijb_u