source: LMDZ5/trunk/libf/dyn3dpar/exner_milieu_p.F @ 1521

Last change on this file since 1521 was 1521, checked in by Ehouarn Millour, 13 years ago

Fix silly bug on wrong sanity check (shame on me).
EM

File size: 5.8 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      logical,save :: firstcall=.true.
53!$OMP THREADPRIVATE(firstcall)
54      character(len=*),parameter :: modname="exner_milieu_p"
55
56      ! Sanity check
57      if (firstcall) then
58        ! check that vertical discretization is compatible
59        ! with this routine
60        if (disvert_type.ne.2) then
61          call abort_gcm(modname,
62     &     "this routine should only be called if disvert_type==2",42)
63        endif
64       
65        ! sanity checks for Shallow Water case (1 vertical layer)
66        if (llm.eq.1) then
67          if (kappa.ne.1) then
68            call abort_gcm(modname,
69     &      "kappa!=1 , but running in Shallow Water mode!!",42)
70          endif
71          if (cpp.ne.r) then
72            call abort_gcm(modname,
73     &      "cpp!=r , but running in Shallow Water mode!!",42)
74          endif
75        endif ! of if (llm.eq.1)
76
77        firstcall=.false.
78      endif ! of if (firstcall)
79     
80c$OMP BARRIER
81
82! Specific behaviour for Shallow Water (1 vertical layer) case
83      if (llm.eq.1) then
84             
85        ! Compute pks(:),pk(:),pkf(:)
86        ijb=ij_begin
87        ije=ij_end
88!$OMP DO SCHEDULE(STATIC)
89        DO ij=ijb, ije
90          pks(ij)=(cpp/preff)*ps(ij)
91          pk(ij,1) = .5*pks(ij)
92          pkf(ij,1)=pk(ij,1)
93        ENDDO
94!$OMP ENDDO
95
96!$OMP MASTER
97      if (pole_nord) then
98        DO  ij   = 1, iim
99          ppn(ij) = aire(   ij   ) * pks(  ij     )
100        ENDDO
101        xpn      = SSUM(iim,ppn,1) /apoln
102 
103        DO ij   = 1, iip1
104          pks(   ij     )  =  xpn
105          pk(ij,1) = .5*pks(ij)
106          pkf(ij,1)=pk(ij,1)
107        ENDDO
108      endif
109     
110      if (pole_sud) then
111        DO  ij   = 1, iim
112          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
113        ENDDO
114        xps      = SSUM(iim,pps,1) /apols
115 
116        DO ij   = 1, iip1
117          pks( ij+ip1jm )  =  xps
118          pk(ij+ip1jm,1)=.5*pks(ij+ip1jm)
119          pkf(ij+ip1jm,1)=pk(ij+ip1jm,1)
120        ENDDO
121      endif
122!$OMP END MASTER
123
124        jjb=jj_begin
125        jje=jj_end
126        CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
127
128        ! our work is done, exit routine
129        return
130      endif ! of if (llm.eq.1)
131
132!!!! General case:
133
134c     -------------
135c     Calcul de pks
136c     -------------
137   
138      ijb=ij_begin
139      ije=ij_end
140
141c$OMP DO SCHEDULE(STATIC)
142      DO   ij  = ijb, ije
143        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
144      ENDDO
145c$OMP ENDDO
146c Synchro OPENMP ici
147
148c$OMP MASTER
149      if (pole_nord) then
150        DO  ij   = 1, iim
151          ppn(ij) = aire(   ij   ) * pks(  ij     )
152        ENDDO
153        xpn      = SSUM(iim,ppn,1) /apoln
154 
155        DO ij   = 1, iip1
156          pks(   ij     )  =  xpn
157        ENDDO
158      endif
159     
160      if (pole_sud) then
161        DO  ij   = 1, iim
162          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
163        ENDDO
164        xps      = SSUM(iim,pps,1) /apols
165 
166        DO ij   = 1, iip1
167          pks( ij+ip1jm )  =  xps
168        ENDDO
169      endif
170c$OMP END MASTER
171c
172c
173c    .... Calcul de pk  pour la couche l
174c    --------------------------------------------
175c
176      dum1 = cpp * (2*preff)**(-kappa)
177      DO l = 1, llm-1
178c$OMP DO SCHEDULE(STATIC)
179        DO   ij   = ijb, ije
180         pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
181        ENDDO
182c$OMP ENDDO NOWAIT       
183      ENDDO
184
185c    .... Calcul de pk  pour la couche l = llm ..
186c    (on met la meme distance (en log pression)  entre Pk(llm)
187c    et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
188
189c$OMP DO SCHEDULE(STATIC)
190      DO   ij   = ijb, ije
191         pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
192      ENDDO
193c$OMP ENDDO NOWAIT       
194
195
196c    calcul de pkf
197c    -------------
198c      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
199      DO l = 1, llm
200c$OMP DO SCHEDULE(STATIC)
201         DO   ij   = ijb, ije
202           pkf(ij,l)=pk(ij,l)
203         ENDDO
204c$OMP ENDDO NOWAIT             
205      ENDDO
206
207c$OMP BARRIER
208     
209      jjb=jj_begin
210      jje=jj_end
211      CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
212     
213c    EST-CE UTILE ?? : calcul de beta
214c    --------------------------------
215      DO l = 2, llm
216c$OMP DO SCHEDULE(STATIC)
217        DO   ij   = ijb, ije
218          beta(ij,l) = pk(ij,l) / pk(ij,l-1)   
219        ENDDO
220c$OMP ENDDO NOWAIT             
221      ENDDO
222
223      RETURN
224      END
Note: See TracBrowser for help on using the repository browser.