LMDZ
diverg_gam_p.F
Go to the documentation of this file.
1  SUBROUTINE diverg_gam_p(klevel,cuvscvgam,cvuscugam,unsairegam ,
2  * unsapolnga,unsapolsga, x, y, div )
3 c
4 c P. Le Van
5 c
6 c *********************************************************************
7 c ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
8 c x et y...
9 c x et y etant des composantes covariantes ...
10 c *********************************************************************
11  USE parallel_lmdz
12  IMPLICIT NONE
13 c
14 c x et y sont des arguments d'entree pour le s-prog
15 c div est un argument de sortie pour le s-prog
16 c
17 c
18 c ---------------------------------------------------------------------
19 c
20 c ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/ .
21 c
22 c ---------------------------------------------------------------------
23 #include "dimensions.h"
24 #include "paramet.h"
25 #include "comgeom.h"
26 c
27 c .......... variables en arguments ...................
28 c
29  INTEGER klevel
30  REAL x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
31  REAL cuvscvgam(ip1jm),cvuscugam(ip1jmp1),unsairegam(ip1jmp1)
32  REAL unsapolnga,unsapolsga
33 c
34 c ............... variables locales .........................
35 
36  REAL aiy1( iip1 ) , aiy2( iip1 )
37  REAL sumypn,sumyps
38  INTEGER l,ij
39 c ...................................................................
40 c
41  EXTERNAL ssum
42  REAL SSUM
43  INTEGER :: ijb,ije,jjb,jje
44 c
45 c
46  ijb=ij_begin
47  ije=ij_end
48  if (pole_nord) ijb=ij_begin+iip1
49  if(pole_sud) ije=ij_end-iip1
50 
51 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
52  DO 10 l = 1,klevel
53 c
54  DO ij = ijb, ije - 1
55  div( ij + 1, l ) = (
56  * cvuscugam( ij+1 ) * x( ij+1,l ) - cvuscugam( ij ) * x( ij , l) +
57  * cuvscvgam(ij-iim) * y(ij-iim,l) - cuvscvgam(ij+1) * y(ij+1,l) )*
58  * unsairegam( ij+1 )
59  ENDDO
60 c
61 c .... correction pour div( 1,j,l) ......
62 c .... div(1,j,l)= div(iip1,j,l) ....
63 c
64 CDIR$ IVDEP
65  DO ij = ijb,ije,iip1
66  div( ij,l ) = div( ij + iim,l )
67  ENDDO
68 c
69 c .... calcul aux poles .....
70 c
71  if (pole_nord) then
72  DO ij = 1,iim
73  aiy1(ij) = cuvscvgam( ij ) * y( ij , l )
74  ENDDO
75  sumypn = ssum( iim,aiy1,1 ) * unsapolnga
76 c
77  DO ij = 1,iip1
78  div( ij , l ) = - sumypn
79  ENDDO
80  endif
81 
82  if (pole_sud) then
83  DO ij = 1,iim
84  aiy2(ij) = cuvscvgam( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
85  ENDDO
86  sumyps = ssum( iim,aiy2,1 ) * unsapolsga
87 c
88  DO ij = 1,iip1
89  div( ij + ip1jm, l ) = sumyps
90  ENDDO
91  endif
92  10 CONTINUE
93 c$OMP END DO NOWAIT
94 c
95 
96  RETURN
97  END
!$Header llmm1 INTEGER ip1jmi1
Definition: paramet.h:14
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
integer, save ij_end
logical, save pole_sud
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
logical, save pole_nord
subroutine diverg_gam_p(klevel, cuvscvgam, cvuscugam, unsairegam, unsapolnga, unsapolsga, x, y, div)
Definition: diverg_gam_p.F:3
!$Header!c c INCLUDE fxyprim h c c c Fonctions in line c c REAL fyprim REAL rj c c il faut la calculer avant d appeler ces fonctions c c c Fonctions a changer selon x(x) et y(y) choisis.c-----------------------------------------------------------------c c.....ici
integer, save ij_begin
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
real function ssum(n, sx, incx)
Definition: cray.F:27