My Project
 All Classes Files Functions Variables Macros
diverg_gam_loc.F
Go to the documentation of this file.
1  SUBROUTINE diverg_gam_loc(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
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( ijb_u:ije_u,klevel ),y( ijb_v:ije_v,klevel )
31  REAL div( ijb_u:ije_u,klevel )
32  REAL cuvscvgam(ip1jm),cvuscugam(ip1jmp1),unsairegam(ip1jmp1)
33  REAL unsapolnga,unsapolsga
34 c
35 c ............... variables locales .........................
36 
37  REAL aiy1( iip1 ) , aiy2( iip1 )
38  REAL sumypn,sumyps
39  INTEGER l,ij
40 c ...................................................................
41 c
42  EXTERNAL ssum
43  REAL ssum
44  INTEGER :: ijb,ije,jjb,jje
45 c
46 c
47  ijb=ij_begin
48  ije=ij_end
49  if (pole_nord) ijb=ij_begin+iip1
50  if(pole_sud) ije=ij_end-iip1
51 
52 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
53  DO 10 l = 1,klevel
54 c
55  DO ij = ijb, ije - 1
56  div( ij + 1, l ) = (
57  * cvuscugam( ij+1 ) * x( ij+1,l ) - cvuscugam( ij ) * x( ij , l) +
58  * cuvscvgam(ij-iim) * y(ij-iim,l) - cuvscvgam(ij+1) * y(ij+1,l) )*
59  * unsairegam( ij+1 )
60  ENDDO
61 c
62 c .... correction pour div( 1,j,l) ......
63 c .... div(1,j,l)= div(iip1,j,l) ....
64 c
65 CDIR$ IVDEP
66  DO ij = ijb,ije,iip1
67  div( ij,l ) = div( ij + iim,l )
68  ENDDO
69 c
70 c .... calcul aux poles .....
71 c
72  if (pole_nord) then
73  DO ij = 1,iim
74  aiy1(ij) = cuvscvgam( ij ) * y( ij , l )
75  ENDDO
76  sumypn = ssum( iim,aiy1,1 ) * unsapolnga
77 c
78  DO ij = 1,iip1
79  div( ij , l ) = - sumypn
80  ENDDO
81  endif
82 
83  if (pole_sud) then
84  DO ij = 1,iim
85  aiy2(ij) = cuvscvgam( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
86  ENDDO
87  sumyps = ssum( iim,aiy2,1 ) * unsapolsga
88 c
89  DO ij = 1,iip1
90  div( ij + ip1jm, l ) = sumyps
91  ENDDO
92  endif
93  10 CONTINUE
94 c$OMP END DO NOWAIT
95 c
96 
97  RETURN
98  END