source: LMDZ5/branches/testing/libf/dyn3dmem/exner_hyb_loc.F @ 1669

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

Version testing basée sur la r1668

http://lmdz.lmd.jussieu.fr/utilisateurs/distribution-du-modele/versions-intermediaires


Testing release based on r1668

File size: 6.0 KB
Line 
1c
2c $Id$
3c
4      SUBROUTINE  exner_hyb_loc(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      USE mod_filtreg_p
33      USE write_field_loc
34      IMPLICIT NONE
35c
36#include "dimensions.h"
37#include "paramet.h"
38#include "comconst.h"
39#include "comgeom.h"
40#include "comvert.h"
41#include "serre.h"
42
43      INTEGER  ngrid
44      REAL p(ijb_u:ije_u,llmp1),pk(ijb_u:ije_u,llm)
45      REAL pkf(ijb_u:ije_u,llm)
46      REAL ps(ijb_u:ije_u),pks(ijb_u:ije_u)
47      REAL alpha(ijb_u:ije_u,llm),beta(ijb_u:ije_u,llm)
48
49c    .... variables locales   ...
50
51      INTEGER l, ij
52      REAL unpl2k,dellta
53
54      REAL ppn(iim),pps(iim)
55      REAL xpn, xps
56      REAL SSUM
57      EXTERNAL SSUM
58      INTEGER ije,ijb,jje,jjb
59c
60c$OMP BARRIER           
61
62      if (llm.eq.1) then
63        ! Specific behaviour for Shallow Water (1 vertical layer) case
64     
65        ! Sanity checks
66        if (kappa.ne.1) then
67          call abort_gcm("exner_hyb",
68     &    "kappa!=1 , but running in Shallow Water mode!!",42)
69        endif
70        if (cpp.ne.r) then
71        call abort_gcm("exner_hyb",
72     &    "cpp!=r , but running in Shallow Water mode!!",42)
73        endif
74       
75        ! Compute pks(:),pk(:),pkf(:)
76        ijb=ij_begin
77        ije=ij_end
78!$OMP DO SCHEDULE(STATIC)
79        DO ij=ijb, ije
80          pks(ij)=(cpp/preff)*ps(ij)
81          pk(ij,1) = .5*pks(ij)
82          pkf(ij,1)=pk(ij,1)
83        ENDDO
84!$OMP ENDDO
85
86!$OMP MASTER
87      if (pole_nord) then
88        DO  ij   = 1, iim
89          ppn(ij) = aire(   ij   ) * pks(  ij     )
90        ENDDO
91        xpn      = SSUM(iim,ppn,1) /apoln
92 
93        DO ij   = 1, iip1
94          pks(   ij     )  =  xpn
95          pk(ij,1) = .5*pks(ij)
96          pkf(ij,1)=pk(ij,1)
97        ENDDO
98      endif
99     
100      if (pole_sud) then
101        DO  ij   = 1, iim
102          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
103        ENDDO
104        xps      = SSUM(iim,pps,1) /apols
105 
106        DO ij   = 1, iip1
107          pks( ij+ip1jm )  =  xps
108          pk(ij+ip1jm,1)=.5*pks(ij+ip1jm)
109          pkf(ij+ip1jm,1)=pk(ij+ip1jm,1)
110        ENDDO
111      endif
112!$OMP END MASTER
113
114        jjb=jj_begin
115        jje=jj_end
116        CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm,
117     &                 2, 1, .TRUE., 1 )
118
119        ! our work is done, exit routine
120        return
121      endif ! of if (llm.eq.1)
122
123
124      unpl2k    = 1.+ 2.* kappa
125c
126      ijb=ij_begin
127      ije=ij_end
128
129c$OMP DO SCHEDULE(STATIC)
130      DO   ij  = ijb, ije
131        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
132      ENDDO
133c$OMP ENDDO
134c Synchro OPENMP ici
135
136c$OMP MASTER
137      if (pole_nord) then
138        DO  ij   = 1, iim
139          ppn(ij) = aire(   ij   ) * pks(  ij     )
140        ENDDO
141        xpn      = SSUM(iim,ppn,1) /apoln
142 
143        DO ij   = 1, iip1
144          pks(   ij     )  =  xpn
145        ENDDO
146      endif
147     
148      if (pole_sud) then
149        DO  ij   = 1, iim
150          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
151        ENDDO
152        xps      = SSUM(iim,pps,1) /apols
153 
154        DO ij   = 1, iip1
155          pks( ij+ip1jm )  =  xps
156        ENDDO
157      endif
158c$OMP END MASTER
159c$OMP BARRIER
160c
161c
162c    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
163c
164c$OMP DO SCHEDULE(STATIC)
165      DO     ij      = ijb,ije
166       alpha(ij,llm) = 0.
167       beta (ij,llm) = 1./ unpl2k
168      ENDDO
169c$OMP ENDDO NOWAIT
170c
171c     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
172c
173      DO l = llm -1 , 2 , -1
174c
175c$OMP DO SCHEDULE(STATIC)
176        DO ij = ijb, ije
177        dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
178        alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
179        beta (ij,l)  =   p(ij,l  ) / dellta   
180        ENDDO
181c$OMP ENDDO NOWAIT
182c
183      ENDDO
184
185c
186c  ***********************************************************************
187c     .....  Calcul de pk pour la couche 1 , pres du sol  ....
188c
189c$OMP DO SCHEDULE(STATIC)
190      DO   ij   = ijb, ije
191       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  /
192     *    (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
193      ENDDO
194c$OMP ENDDO NOWAIT
195c
196c    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
197c
198      DO l = 2, llm
199c$OMP DO SCHEDULE(STATIC)
200        DO   ij   = ijb, ije
201         pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
202        ENDDO
203c$OMP ENDDO NOWAIT       
204      ENDDO
205c
206c
207c      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
208      DO l = 1, llm
209c$OMP DO SCHEDULE(STATIC)
210         DO   ij   = ijb, ije
211           pkf(ij,l)=pk(ij,l)
212         ENDDO
213c$OMP ENDDO NOWAIT             
214      ENDDO
215
216c$OMP BARRIER
217     
218      jjb=jj_begin
219      jje=jj_end
220#ifdef DEBUG_IO   
221      call WriteField_u('pkf',pkf)
222#endif
223      CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm,
224     &                 2, 1, .TRUE., 1 )
225#ifdef DEBUG_IO   
226      call WriteField_u('pkf',pkf)
227#endif     
228
229      RETURN
230      END
Note: See TracBrowser for help on using the repository browser.