My Project
 All Classes Files Functions Variables Macros
divergf_p.F
Go to the documentation of this file.
1  SUBROUTINE divergf_p(klevel,x,y,div)
2 c
3 c P. Le Van
4 c
5 c *********************************************************************
6 c ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
7 c x et y...
8 c x et y etant des composantes covariantes ...
9 c *********************************************************************
10  USE parallel
11  IMPLICIT NONE
12 c
13 c x et y sont des arguments d'entree pour le s-prog
14 c div est un argument de sortie pour le s-prog
15 c
16 c
17 c ---------------------------------------------------------------------
18 c
19 c ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/ .
20 c
21 c ---------------------------------------------------------------------
22 #include "dimensions.h"
23 #include "paramet.h"
24 #include "comgeom.h"
25 c
26 c .......... variables en arguments ...................
27 c
28  INTEGER klevel
29  REAL x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
30  INTEGER l,ij
31 c
32 c ............... variables locales .........................
33 
34  REAL aiy1( iip1 ) , aiy2( iip1 )
35  REAL sumypn,sumyps
36 c ...................................................................
37 c
38  EXTERNAL ssum
39  REAL ssum
40  INTEGER :: ijb,ije,jjb,jje
41 c
42 c
43  ijb=ij_begin
44  ije=ij_end
45  if (pole_nord) ijb=ij_begin+iip1
46  if(pole_sud) ije=ij_end-iip1
47 
48 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
49  DO 10 l = 1,klevel
50 c
51  DO ij = ijb, ije - 1
52  div( ij + 1, l ) =
53  * cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) +
54  * cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)
55  ENDDO
56 
57 c
58 c .... correction pour div( 1,j,l) ......
59 c .... div(1,j,l)= div(iip1,j,l) ....
60 c
61 CDIR$ IVDEP
62  DO ij = ijb,ije,iip1
63  div( ij,l ) = div( ij + iim,l )
64  ENDDO
65 c
66 c .... calcul aux poles .....
67 c
68  if (pole_nord) then
69 
70  DO ij = 1,iim
71  aiy1(ij) = cuvsurcv( ij ) * y( ij , l )
72  ENDDO
73  sumypn = ssum( iim,aiy1,1 ) / apoln
74 
75 c
76  DO ij = 1,iip1
77  div( ij , l ) = - sumypn
78  ENDDO
79 
80  endif
81 
82  if (pole_sud) then
83 
84  DO ij = 1,iim
85  aiy2(ij) = cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
86  ENDDO
87  sumyps = ssum( iim,aiy2,1 ) / apols
88 c
89  DO ij = 1,iip1
90  div( ij + ip1jm, l ) = sumyps
91  ENDDO
92 
93  endif
94 
95  10 CONTINUE
96 c$OMP END DO NOWAIT
97 
98 c
99  jjb=jj_begin
100  jje=jj_end
101  if (pole_sud) jje=jj_end-1
102 
103  CALL filtreg_p( div,jjb,jje, jjp1, klevel, 2, 2, .true., 1 )
104 
105 c
106 c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
107  DO l = 1, klevel
108  DO ij = ijb,ije
109  div(ij,l) = div(ij,l) * unsaire(ij)
110  ENDDO
111  ENDDO
112 c$OMP END DO NOWAIT
113 c
114  RETURN
115  END