source: trunk/libf/dyn3dpar/exner_milieu_p.F @ 124

Last change on this file since 124 was 124, checked in by emillour, 14 years ago

EM: suite mise au point discretisation verticale et quelques corrections de bugs dans le version de reference parallele.

File size: 5.2 KB
Line 
1!
2! $Id $
3!
4      SUBROUTINE  exner_milieu_p ( ngrid, ps, p,beta, pks, pk, pkf )
5c
6c     Auteurs :  F. Forget , Y. Wanherdrick
7c P.Le Van  , Fr. Hourdin  .
8c    ..........
9c
10c    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
11c    .... beta, pks,pk,pkf   sont des argum.de sortie au sous-prog ...
12c
13c   ************************************************************************
14c    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
15c    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
16c    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
17c   ************************************************************************
18c    .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
19c    la pression et la fonction d'Exner  au  sol  .
20c
21c     WARNING : CECI est une version speciale de exner_hyb originale
22c               Utilise dans la version martienne pour pouvoir
23c               tourner avec des coordonnees verticales complexe
24c              => Il ne verifie PAS la condition la proportionalite en
25c              energie totale/ interne / potentielle (F.Forget 2001)
26c    ( voir note de Fr.Hourdin )  ,
27c
28      USE parallel
29      IMPLICIT NONE
30c
31#include "dimensions.h"
32#include "paramet.h"
33#include "comconst.h"
34#include "comgeom.h"
35#include "comvert.h"
36#include "serre.h"
37
38      INTEGER  ngrid
39      REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
40      REAL ps(ngrid),pks(ngrid), beta(ngrid,llm)
41
42c    .... variables locales   ...
43
44      INTEGER l, ij
45      REAL dum1
46
47      REAL ppn(iim),pps(iim)
48      REAL xpn, xps
49      REAL SSUM
50      EXTERNAL SSUM
51      INTEGER ije,ijb,jje,jjb
52     
53c$OMP BARRIER
54
55      if (llm.eq.1) then
56        ! Specific behaviour for Shallow Water (1 vertical layer) case
57     
58        ! Sanity checks
59        if (kappa.ne.1) then
60          call abort_gcm("exner_hyb",
61     &    "kappa!=1 , but running in Shallow Water mode!!",42)
62        endif
63        if (cpp.ne.r) then
64        call abort_gcm("exner_hyb",
65     &    "cpp!=r , but running in Shallow Water mode!!",42)
66        endif
67       
68        ! Compute pks(:),pk(:),pkf(:)
69        ijb=ij_begin
70        ije=ij_end
71!$OMP DO SCHEDULE(STATIC)
72        DO ij=ijb, ije
73          pks(ij)=(cpp/preff)*ps(ij)
74          pk(ij,1) = .5*pks(ij)
75          pkf(ij,1)=pk(ij,1)
76        ENDDO
77!$OMP ENDDO
78
79!$OMP MASTER
80      if (pole_nord) then
81        DO  ij   = 1, iim
82          ppn(ij) = aire(   ij   ) * pks(  ij     )
83        ENDDO
84        xpn      = SSUM(iim,ppn,1) /apoln
85 
86        DO ij   = 1, iip1
87          pks(   ij     )  =  xpn
88          pk(ij,1) = .5*pks(ij)
89          pkf(ij,1)=pk(ij,1)
90        ENDDO
91      endif
92     
93      if (pole_sud) then
94        DO  ij   = 1, iim
95          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
96        ENDDO
97        xps      = SSUM(iim,pps,1) /apols
98 
99        DO ij   = 1, iip1
100          pks( ij+ip1jm )  =  xps
101          pk(ij+ip1jm,1)=.5*pks(ij+ip1jm)
102          pkf(ij+ip1jm,1)=pk(ij+ip1jm,1)
103        ENDDO
104      endif
105!$OMP END MASTER
106
107        jjb=jj_begin
108        jje=jj_end
109        CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
110
111        ! our work is done, exit routine
112        return
113      endif ! of if (llm.eq.1)
114
115c     -------------
116c     Calcul de pks
117c     -------------
118   
119      ijb=ij_begin
120      ije=ij_end
121
122c$OMP DO SCHEDULE(STATIC)
123      DO   ij  = ijb, ije
124        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
125      ENDDO
126c$OMP ENDDO
127c Synchro OPENMP ici
128
129c$OMP MASTER
130      if (pole_nord) then
131        DO  ij   = 1, iim
132          ppn(ij) = aire(   ij   ) * pks(  ij     )
133        ENDDO
134        xpn      = SSUM(iim,ppn,1) /apoln
135 
136        DO ij   = 1, iip1
137          pks(   ij     )  =  xpn
138        ENDDO
139      endif
140     
141      if (pole_sud) then
142        DO  ij   = 1, iim
143          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
144        ENDDO
145        xps      = SSUM(iim,pps,1) /apols
146 
147        DO ij   = 1, iip1
148          pks( ij+ip1jm )  =  xps
149        ENDDO
150      endif
151c$OMP END MASTER
152c
153c
154c    .... Calcul de pk  pour la couche l
155c    --------------------------------------------
156c
157      dum1 = cpp * (2*preff)**(-kappa)
158      DO l = 1, llm-1
159c$OMP DO SCHEDULE(STATIC)
160        DO   ij   = ijb, ije
161         pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
162        ENDDO
163c$OMP ENDDO NOWAIT       
164      ENDDO
165
166c    .... Calcul de pk  pour la couche l = llm ..
167c    (on met la meme distance (en log pression)  entre Pk(llm)
168c    et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
169
170c$OMP DO SCHEDULE(STATIC)
171      DO   ij   = ijb, ije
172         pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
173      ENDDO
174c$OMP ENDDO NOWAIT       
175
176
177c    calcul de pkf
178c    -------------
179c      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
180      DO l = 1, llm
181c$OMP DO SCHEDULE(STATIC)
182         DO   ij   = ijb, ije
183           pkf(ij,l)=pk(ij,l)
184         ENDDO
185c$OMP ENDDO NOWAIT             
186      ENDDO
187
188c$OMP BARRIER
189     
190      jjb=jj_begin
191      jje=jj_end
192      CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
193     
194c    EST-CE UTILE ?? : calcul de beta
195c    --------------------------------
196      DO l = 2, llm
197c$OMP DO SCHEDULE(STATIC)
198        DO   ij   = ijb, ije
199          beta(ij,l) = pk(ij,l) / pk(ij,l-1)   
200        ENDDO
201c$OMP ENDDO NOWAIT             
202      ENDDO
203
204      RETURN
205      END
Note: See TracBrowser for help on using the repository browser.