source: LMDZ5/trunk/libf/dyn3dmem/divergf_loc.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: 3.0 KB
Line 
1      SUBROUTINE divergf_loc(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      USE mod_filtreg_p
12      IMPLICIT NONE
13c
14c      x  et  y  sont des arguments  d'entree pour le s-prog
15c        div      est  un argument  de sortie pour le s-prog
16c
17c
18c   ---------------------------------------------------------------------
19c
20c    ATTENTION : pendant ce s-pg , ne pas toucher au COMMON/scratch/  .
21c
22c   ---------------------------------------------------------------------
23#include "dimensions.h"
24#include "paramet.h"
25#include "comgeom.h"
26c
27c    ..........          variables en arguments    ...................
28c
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      INTEGER   l,ij
33c
34c    ...............     variables  locales   .........................
35
36      REAL aiy1( iip1 ) , aiy2( iip1 )
37      REAL sumypn,sumyps
38c    ...................................................................
39c
40      EXTERNAL  SSUM
41      REAL      SSUM
42      INTEGER :: ijb,ije,jjb,jje
43c
44c
45      ijb=ij_begin
46      ije=ij_end
47      if (pole_nord) ijb=ij_begin+iip1
48      if(pole_sud)  ije=ij_end-iip1
49
50c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)       
51      DO 10 l = 1,klevel
52c
53        DO  ij = ijb, ije - 1
54         div( ij + 1, l )     = 
55     *   cvusurcu( ij+1 ) * x( ij+1,l ) - cvusurcu( ij ) * x( ij , l) +
56     *   cuvsurcv(ij-iim) * y(ij-iim,l) - cuvsurcv(ij+1) * y(ij+1,l)
57        ENDDO
58
59c
60c     ....  correction pour  div( 1,j,l)  ......
61c     ....   div(1,j,l)= div(iip1,j,l) ....
62c
63CDIR$ IVDEP
64        DO  ij = ijb,ije,iip1
65         div( ij,l ) = div( ij + iim,l )
66        ENDDO
67c
68c     ....  calcul  aux poles  .....
69c
70        if (pole_nord) then
71       
72          DO  ij  = 1,iim
73           aiy1(ij) =    cuvsurcv(    ij       ) * y(     ij     , l )
74          ENDDO
75          sumypn = SSUM ( iim,aiy1,1 ) / apoln
76
77c
78          DO  ij = 1,iip1
79           div(     ij    , l ) = - sumypn
80          ENDDO
81         
82        endif
83       
84        if (pole_sud) then
85       
86          DO  ij  = 1,iim
87           aiy2(ij) =    cuvsurcv( ij+ ip1jmi1 ) * y( ij+ ip1jmi1, l )
88          ENDDO
89          sumyps = SSUM ( iim,aiy2,1 ) / apols
90c
91          DO  ij = 1,iip1
92           div( ij + ip1jm, l ) =   sumyps
93          ENDDO
94         
95        endif
96       
97  10    CONTINUE
98c$OMP END DO NOWAIT
99
100c
101        jjb=jj_begin
102        jje=jj_end
103        if (pole_sud) jje=jj_end-1
104       
105        CALL filtreg_p( div,jjb_u,jje_u,jjb,jje, jjp1,
106     &                   klevel, 2, 2, .TRUE., 1 )
107     
108c
109c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
110        DO l = 1, klevel
111           DO ij = ijb,ije
112            div(ij,l) = div(ij,l) * unsaire(ij)
113          ENDDO
114        ENDDO
115c$OMP END DO NOWAIT
116c
117       RETURN
118       END
Note: See TracBrowser for help on using the repository browser.