source: LMDZ4/trunk/libf/dyn3dpar/exner_hyb_p.F @ 774

Last change on this file since 774 was 774, checked in by Laurent Fairhead, 17 years ago

Suite du merge entre la version et la HEAD: quelques modifications de
Yann sur le

LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.8 KB
Line 
1      SUBROUTINE  exner_hyb_p ( ngrid, ps, p,alpha,beta, pks, pk, pkf )
2c
3c     Auteurs :  P.Le Van  , Fr. Hourdin  .
4c    ..........
5c
6c    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
7c    .... alpha,beta, pks,pk,pkf   sont des argum.de sortie au sous-prog ...
8c
9c   ************************************************************************
10c    Calcule la fonction d'Exner pk = Cp * p ** kappa , aux milieux des
11c    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
12c    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
13c   ************************************************************************
14c  .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
15c    la pression et la fonction d'Exner  au  sol  .
16c
17c                                 -------- z                                   
18c    A partir des relations  ( 1 ) p*dz(pk) = kappa *pk*dz(p)      et
19c                            ( 2 ) pk(l) = alpha(l)+ beta(l)*pk(l-1)
20c    ( voir note de Fr.Hourdin )  ,
21c
22c    on determine successivement , du haut vers le bas des couches, les
23c    coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2),
24c    puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches, 
25c     pk(ij,l)  donne  par la relation (2),  pour l = 2 a l = llm .
26c
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), alpha(ngrid,llm),beta(ngrid,llm)
41
42c    .... variables locales   ...
43
44      INTEGER l, ij
45      REAL unpl2k,dellta
46
47      REAL ppn(iim),pps(iim)
48      REAL xpn, xps
49      REAL SSUM
50      EXTERNAL SSUM
51      INTEGER ije,ijb,jje,jjb
52c
53c$OMP MASTER           
54      unpl2k    = 1.+ 2.* kappa
55c
56      ijb=ij_begin
57      ije=ij_end
58
59
60      DO   ij  = ijb, ije
61        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
62      ENDDO
63
64      if (pole_nord) then
65        DO  ij   = 1, iim
66          ppn(ij) = aire(   ij   ) * pks(  ij     )
67        ENDDO
68        xpn      = SSUM(iim,ppn,1) /apoln
69 
70        DO ij   = 1, iip1
71          pks(   ij     )  =  xpn
72        ENDDO
73      endif
74     
75      if (pole_sud) then
76        DO  ij   = 1, iim
77          pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
78        ENDDO
79        xps      = SSUM(iim,pps,1) /apols
80 
81        DO ij   = 1, iip1
82          pks( ij+ip1jm )  =  xps
83        ENDDO
84      endif
85
86c
87c
88c    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
89c
90      DO     ij      = ijb,ije
91       alpha(ij,llm) = 0.
92       beta (ij,llm) = 1./ unpl2k
93      ENDDO
94c
95c     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
96c
97      DO l = llm -1 , 2 , -1
98c
99        DO ij = ijb, ije
100        dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
101        alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
102        beta (ij,l)  =   p(ij,l  ) / dellta   
103        ENDDO
104c
105      ENDDO
106
107c
108c  ***********************************************************************
109c     .....  Calcul de pk pour la couche 1 , pres du sol  ....
110c
111
112      DO   ij   = ijb, ije
113       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  /
114     *    (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
115      ENDDO
116c
117c    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
118c
119      DO l = 2, llm
120        DO   ij   = ijb, ije
121         pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
122        ENDDO
123      ENDDO
124c
125c
126c      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
127      pkf(ijb:ije,1:llm)=pk(ijb:ije,1:llm)
128c$OMP END MASTER
129c$OMP BARRIER
130     
131      jjb=jj_begin
132      jje=jj_end
133      CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
134     
135
136      RETURN
137      END
Note: See TracBrowser for help on using the repository browser.