LMDZ
tourpot_p.F
Go to the documentation of this file.
1  SUBROUTINE tourpot_p ( vcov, ucov, massebxy, vorpot )
3  IMPLICIT NONE
4 
5 c=======================================================================
6 c
7 c Auteur: P. Le Van
8 c -------
9 c
10 c Objet:
11 c ------
12 c
13 c *******************************************************************
14 c ......... calcul du tourbillon potentiel .........
15 c *******************************************************************
16 c
17 c vcov,ucov,fext et pbarxyfl sont des argum. d'entree pour le s-pg .
18 c vorpot est un argum.de sortie pour le s-pg .
19 c
20 c=======================================================================
21 
22 #include "dimensions.h"
23 #include "paramet.h"
24 #include "comgeom.h"
25 #include "logic.h"
26 
27  REAL rot( ip1jm,llm )
28  REAL vcov( ip1jm,llm ),ucov( ip1jmp1,llm )
29  REAL massebxy( ip1jm,llm ),vorpot( ip1jm,llm )
30 
31  INTEGER l, ij ,ije,ijb,jje,jjb
32 
33 
34  ijb=ij_begin-iip1
35  ije=ij_end
36 
37  if (pole_nord) ijb=ij_begin
38 
39 
40 c ... vorpot = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) /psbarxy ..
41 
42 
43 
44 c ........ Calcul du rotationnel du vent V puis filtrage ........
45 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
46  DO 5 l = 1,llm
47 
48  if (pole_sud) ije=ij_end-iip1-1
49  DO 2 ij = ijb, ije
50  rot( ij,l ) = vcov(ij+1,l)-vcov(ij,l)+ucov(ij+iip1,l)-ucov(ij,l)
51  2 CONTINUE
52 
53 c .... correction pour rot( iip1,j,l ) .....
54 c .... rot(iip1,j,l) = rot(1,j,l) .....
55 
56 CDIR$ IVDEP
57 
58  if (pole_sud) ije=ij_end-iip1
59 
60  DO 3 ij = ijb+iip1-1, ije, iip1
61  rot( ij,l ) = rot( ij -iim, l )
62  3 CONTINUE
63 
64  5 CONTINUE
65 c$OMP END DO NOWAIT
66  jjb=jj_begin-1
67  jje=jj_end
68 
69  if (pole_nord) jjb=jjb+1
70  if (pole_sud) jje=jje-1
71  CALL filtreg_p( rot, jjb,jje,jjm, llm, 2, 1, .false., 1 )
72 
73 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
74  DO 10 l = 1, llm
75 
76  if (pole_sud) ije=ij_end-iip1-1
77 
78  DO 6 ij = ijb, ije
79  vorpot( ij,l ) = ( rot(ij,l) + fext(ij) ) / massebxy(ij,l)
80  6 CONTINUE
81 
82 c ..... correction pour vorpot( iip1,j,l) .....
83 c .... vorpot(iip1,j,l)= vorpot(1,j,l) ....
84 CDIR$ IVDEP
85  if (pole_sud) ije=ij_end-iip1
86  DO 8 ij = ijb+iip1-1, ije, iip1
87  vorpot( ij,l ) = vorpot( ij -iim,l )
88  8 CONTINUE
89 
90  10 CONTINUE
91 c$OMP END DO NOWAIT
92  RETURN
93  END
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
!$Header!CDK comgeom COMMON comgeom && fext
Definition: comgeom.h:25
subroutine filtreg_p(champ, ibeg, iend, nlat, nbniv, ifiltre, iaire, griscal, iter)
Definition: filtreg_p.F:5
integer, save jj_end
subroutine tourpot_p(vcov, ucov, massebxy, vorpot)
Definition: tourpot_p.F: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
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
!$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
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24