source: LMDZ4/tags/LMDZ4_V2/libf/dyn3dpar/divergf_p.F @ 1278

Last change on this file since 1278 was 630, checked in by Laurent Fairhead, 19 years ago

Import d'une version parallele de la dynamique YM
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 2.8 KB
Line 
1      SUBROUTINE divergf_p(klevel,x,y,div)
2c
3c     P. Le Van
4c
5c  *********************************************************************
6c  ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
7c     x et y...
8c              x et y  etant des composantes covariantes   ...
9c  *********************************************************************
10      USE PARALLEL
11      IMPLICIT NONE
12c
13c      x  et  y  sont des arguments  d'entree pour le s-prog
14c        div      est  un argument  de sortie pour le s-prog
15c
16c
17c   ---------------------------------------------------------------------
18c
19c    ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .
20c
21c   ---------------------------------------------------------------------
22#include "dimensions.h"
23#include "paramet.h"
24#include "comgeom.h"
25c
26c    ..........          variables en arguments    ...................
27c
28      INTEGER klevel
29      REAL x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
30      INTEGER   l,ij
31c
32c    ...............     variables  locales   .........................
33
34      REAL aiy1( iip1 ) , aiy2( iip1 )
35      REAL sumypn,sumyps
36c    ...................................................................
37c
38      EXTERNAL  SSUM
39      REAL      SSUM
40      INTEGER :: ijb,ije,jjb,jje
41c
42c
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      DO 10 l = 1,klevel
49c
50        DO  ij = ijb, ije - 1
51         div( ij + 1, l )     = 
52     *   cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) +
53     *   cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)
54        ENDDO
55c
56c     ....  correction pour  div( 1,j,l)  ......
57c     ....   div(1,j,l)= div(iip1,j,l) ....
58c
59CDIR$ IVDEP
60        DO  ij = ijb,ije,iip1
61         div( ij,l ) = div( ij + iim,l )
62        ENDDO
63c
64c     ....  calcul  aux poles  .....
65c
66        if (pole_nord) then
67       
68          DO  ij  = 1,iim
69           aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )
70          ENDDO
71          sumypn = SSUM ( iim,aiy1,1 ) / apoln
72
73c
74          DO  ij = 1,iip1
75           div(     ij    , l ) = - sumypn
76          ENDDO
77         
78        endif
79       
80        if (pole_sud) then
81       
82          DO  ij  = 1,iim
83           aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
84          ENDDO
85          sumyps = SSUM ( iim,aiy2,1 ) / apols
86c
87          DO  ij = 1,iip1
88           div( ij + ip1jm, l ) =   sumyps
89          ENDDO
90         
91        endif
92       
93  10    CONTINUE
94c
95        jjb=jj_begin
96        jje=jj_end
97        if (pole_sud) jje=jj_end-1
98       
99        CALL filtreg_p( div,jjb,jje, jjp1, klevel, 2, 2, .TRUE., 1 )
100     
101c
102        DO l = 1, klevel
103           DO ij = ijb,ije
104            div(ij,l) = div(ij,l) * unsaire(ij)
105          ENDDO
106        ENDDO
107c
108       RETURN
109       END
Note: See TracBrowser for help on using the repository browser.