source: LMDZ5/trunk/libf/dyn3dpar/exner_hyb_p.F @ 1523

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

Implementation of a different vertical discretization (from/for planets, but
can in principle also be used for Earth).
Choice of vertical discretization is set by flag 'disvert_type';
'disvert_type=1' is Earth standard (default; ie set to 1 if
planet_type=="earth") case.
With 'disvert_type=2', approximate altitude of layers and reference atmospheric
scale height must be given using an input file ("z2sig.def", first line
should give scale height, in km, following lines must specify the altitude,
in km above surface, of mid-layers, one per line; see disvert_noterre.F).

Checked that these changes do not impact on 'bench' results, on Vargas.

EM.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.2 KB
Line 
1!
2! $Id $
3!
4      SUBROUTINE  exner_hyb_p ( ngrid, ps, p,alpha,beta, pks, pk, pkf )
5c
6c     Auteurs :  P.Le Van  , Fr. Hourdin  .
7c    ..........
8c
9c    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
10c    .... alpha,beta, pks,pk,pkf   sont des argum.de sortie au sous-prog ...
11c
12c   ************************************************************************
13c    Calcule la fonction d'Exner pk = Cp * p ** kappa , aux milieux des
14c    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
15c    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
16c   ************************************************************************
17c  .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
18c    la pression et la fonction d'Exner  au  sol  .
19c
20c                                 -------- z                                   
21c    A partir des relations  ( 1 ) p*dz(pk) = kappa *pk*dz(p)      et
22c                            ( 2 ) pk(l) = alpha(l)+ beta(l)*pk(l-1)
23c    ( voir note de Fr.Hourdin )  ,
24c
25c    on determine successivement , du haut vers le bas des couches, les
26c    coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2),
27c    puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches, 
28c     pk(ij,l)  donne  par la relation (2),  pour l = 2 a l = llm .
29c
30c
31      USE parallel
32      IMPLICIT NONE
33c
34#include "dimensions.h"
35#include "paramet.h"
36#include "comconst.h"
37#include "comgeom.h"
38#include "comvert.h"
39#include "serre.h"
40
41      INTEGER  ngrid
42      REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
43      REAL ps(ngrid),pks(ngrid), alpha(ngrid,llm),beta(ngrid,llm)
44
45c    .... variables locales   ...
46
47      INTEGER l, ij
48      REAL unpl2k,dellta
49
50      REAL ppn(iim),pps(iim)
51      REAL xpn, xps
52      REAL SSUM
53      EXTERNAL SSUM
54      INTEGER ije,ijb,jje,jjb
55      logical,save :: firstcall=.true.
56!$OMP THREADPRIVATE(firstcall)
57      character(len=*),parameter :: modname="exner_hyb_p"
58c
59
60      ! Sanity check
61      if (firstcall) then
62        ! check that vertical discretization is compatible
63        ! with this routine
64        if (disvert_type.ne.1) then
65          call abort_gcm(modname,
66     &     "this routine should only be called if disvert_type==1",42)
67        endif
68       
69        ! sanity checks for Shallow Water case (1 vertical layer)
70        if (llm.eq.1) then
71          if (kappa.ne.1) then
72            call abort_gcm(modname,
73     &      "kappa!=1 , but running in Shallow Water mode!!",42)
74          endif
75          if (cpp.ne.r) then
76            call abort_gcm(modname,
77     &      "cpp!=r , but running in Shallow Water mode!!",42)
78          endif
79        endif ! of if (llm.eq.1)
80
81        firstcall=.false.
82      endif ! of if (firstcall)
83
84c$OMP BARRIER
85
86! Specific behaviour for Shallow Water (1 vertical layer) case
87      if (llm.eq.1) then
88     
89        ! Compute pks(:),pk(:),pkf(:)
90        ijb=ij_begin
91        ije=ij_end
92!$OMP DO SCHEDULE(STATIC)
93        DO ij=ijb, ije
94          pks(ij)=(cpp/preff)*ps(ij)
95          pk(ij,1) = .5*pks(ij)
96          pkf(ij,1)=pk(ij,1)
97        ENDDO
98!$OMP ENDDO
99
100!$OMP MASTER
101      if (pole_nord) then
102        DO  ij   = 1, iim
103          ppn(ij) = aire(   ij   ) * pks(  ij     )
104        ENDDO
105        xpn      = SSUM(iim,ppn,1) /apoln
106 
107        DO ij   = 1, iip1
108          pks(   ij     )  =  xpn
109          pk(ij,1) = .5*pks(ij)
110          pkf(ij,1)=pk(ij,1)
111        ENDDO
112      endif
113     
114      if (pole_sud) then
115        DO  ij   = 1, iim
116          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
117        ENDDO
118        xps      = SSUM(iim,pps,1) /apols
119 
120        DO ij   = 1, iip1
121          pks( ij+ip1jm )  =  xps
122          pk(ij+ip1jm,1)=.5*pks(ij+ip1jm)
123          pkf(ij+ip1jm,1)=pk(ij+ip1jm,1)
124        ENDDO
125      endif
126!$OMP END MASTER
127
128        jjb=jj_begin
129        jje=jj_end
130        CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
131
132        ! our work is done, exit routine
133        return
134      endif ! of if (llm.eq.1)
135
136!!!! General case:
137
138      unpl2k    = 1.+ 2.* kappa
139c
140      ijb=ij_begin
141      ije=ij_end
142
143c$OMP DO SCHEDULE(STATIC)
144      DO   ij  = ijb, ije
145        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
146      ENDDO
147c$OMP ENDDO
148c Synchro OPENMP ici
149
150c$OMP MASTER
151      if (pole_nord) then
152        DO  ij   = 1, iim
153          ppn(ij) = aire(   ij   ) * pks(  ij     )
154        ENDDO
155        xpn      = SSUM(iim,ppn,1) /apoln
156 
157        DO ij   = 1, iip1
158          pks(   ij     )  =  xpn
159        ENDDO
160      endif
161     
162      if (pole_sud) then
163        DO  ij   = 1, iim
164          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
165        ENDDO
166        xps      = SSUM(iim,pps,1) /apols
167 
168        DO ij   = 1, iip1
169          pks( ij+ip1jm )  =  xps
170        ENDDO
171      endif
172c$OMP END MASTER
173c
174c
175c    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
176c
177c$OMP DO SCHEDULE(STATIC)
178      DO     ij      = ijb,ije
179       alpha(ij,llm) = 0.
180       beta (ij,llm) = 1./ unpl2k
181      ENDDO
182c$OMP ENDDO NOWAIT
183c
184c     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
185c
186      DO l = llm -1 , 2 , -1
187c
188c$OMP DO SCHEDULE(STATIC)
189        DO ij = ijb, ije
190        dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
191        alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
192        beta (ij,l)  =   p(ij,l  ) / dellta   
193        ENDDO
194c$OMP ENDDO NOWAIT
195c
196      ENDDO
197
198c
199c  ***********************************************************************
200c     .....  Calcul de pk pour la couche 1 , pres du sol  ....
201c
202c$OMP DO SCHEDULE(STATIC)
203      DO   ij   = ijb, ije
204       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  /
205     *    (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
206      ENDDO
207c$OMP ENDDO NOWAIT
208c
209c    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
210c
211      DO l = 2, llm
212c$OMP DO SCHEDULE(STATIC)
213        DO   ij   = ijb, ije
214         pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
215        ENDDO
216c$OMP ENDDO NOWAIT       
217      ENDDO
218c
219c
220c      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
221      DO l = 1, llm
222c$OMP DO SCHEDULE(STATIC)
223         DO   ij   = ijb, ije
224           pkf(ij,l)=pk(ij,l)
225         ENDDO
226c$OMP ENDDO NOWAIT             
227      ENDDO
228
229c$OMP BARRIER
230     
231      jjb=jj_begin
232      jje=jj_end
233      CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
234     
235
236      RETURN
237      END
Note: See TracBrowser for help on using the repository browser.