source: LMDZ5/trunk/libf/dyn3dmem/divergf_p.F @ 1632

Last change on this file since 1632 was 1632, checked in by Laurent Fairhead, 12 years ago

Import initial du répertoire dyn3dmem

Attention! ceci n'est qu'une version préliminaire du code "basse mémoire":
le code contenu dans ce répertoire est basé sur la r1320 et a donc besoin
d'être mis à jour par rapport à la dynamique parallèle d'aujourd'hui.
Ce code est toutefois mis à disposition pour circonvenir à des problèmes
de mémoire que certaines configurations du modèle pourraient rencontrer.
Dans l'état, il compile et tourne sur vargas et au CCRT


Initial import of dyn3dmem

Warning! this is just a preliminary version of the memory light code:
it is based on r1320 of the code and thus needs to be updated before
it can replace the present dyn3dpar code. It is nevertheless put at your
disposal to circumvent some memory problems some LMDZ configurations may
encounter. In its present state, it will compile and run on vargas and CCRT

File size: 2.9 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
48c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)       
49      DO 10 l = 1,klevel
50c
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
57c
58c     ....  correction pour  div( 1,j,l)  ......
59c     ....   div(1,j,l)= div(iip1,j,l) ....
60c
61CDIR$ IVDEP
62        DO  ij = ijb,ije,iip1
63         div( ij,l ) = div( ij + iim,l )
64        ENDDO
65c
66c     ....  calcul  aux poles  .....
67c
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
75c
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
88c
89          DO  ij = 1,iip1
90           div( ij + ip1jm, l ) =   sumyps
91          ENDDO
92         
93        endif
94       
95  10    CONTINUE
96c$OMP END DO NOWAIT
97
98c
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     
105c
106c$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
112c$OMP END DO NOWAIT
113c
114       RETURN
115       END
Note: See TracBrowser for help on using the repository browser.