source: LMDZ5/branches/testing/libf/dyn3d_common/exner_hyb.F @ 1999

Last change on this file since 1999 was 1999, checked in by Laurent Fairhead, 10 years ago

Merged trunk changes r1920:1997 into testing branch

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.4 KB
Line 
1!
2! $Id $
3!
4      SUBROUTINE  exner_hyb ( 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      IMPLICIT NONE
32c
33#include "dimensions.h"
34#include "paramet.h"
35#include "comconst.h"
36#include "comgeom.h"
37#include "comvert.h"
38#include "serre.h"
39
40      INTEGER  ngrid
41      REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
42      REAL ps(ngrid),pks(ngrid), alpha(ngrid,llm),beta(ngrid,llm)
43
44c    .... variables locales   ...
45
46      INTEGER l, ij
47      REAL unpl2k,dellta
48
49      REAL ppn(iim),pps(iim)
50      REAL xpn, xps
51      REAL SSUM
52c
53      logical,save :: firstcall=.true.
54      character(len=*),parameter :: modname="exner_hyb"
55     
56      ! Sanity check
57      if (firstcall) then
58        ! sanity checks for Shallow Water case (1 vertical layer)
59        if (llm.eq.1) then
60          if (kappa.ne.1) then
61            call abort_gcm(modname,
62     &      "kappa!=1 , but running in Shallow Water mode!!",42)
63          endif
64          if (cpp.ne.r) then
65            call abort_gcm(modname,
66     &      "cpp!=r , but running in Shallow Water mode!!",42)
67          endif
68        endif ! of if (llm.eq.1)
69
70        firstcall=.false.
71      endif ! of if (firstcall)
72
73      if (llm.eq.1) then
74       
75        ! Compute pks(:),pk(:),pkf(:)
76       
77        DO   ij  = 1, ngrid
78          pks(ij) = (cpp/preff) * ps(ij)
79          pk(ij,1) = .5*pks(ij)
80        ENDDO
81       
82        CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
83        CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
84       
85        ! our work is done, exit routine
86        return
87
88      endif ! of if (llm.eq.1)
89
90!!!! General case:
91     
92      unpl2k    = 1.+ 2.* kappa
93c
94      DO   ij  = 1, ngrid
95        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
96      ENDDO
97
98      DO  ij   = 1, iim
99        ppn(ij) = aire(   ij   ) * pks(  ij     )
100        pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
101      ENDDO
102      xpn      = SSUM(iim,ppn,1) /apoln
103      xps      = SSUM(iim,pps,1) /apols
104
105      DO ij   = 1, iip1
106        pks(   ij     )  =  xpn
107        pks( ij+ip1jm )  =  xps
108      ENDDO
109c
110c
111c    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
112c
113      DO     ij      = 1, ngrid
114       alpha(ij,llm) = 0.
115       beta (ij,llm) = 1./ unpl2k
116      ENDDO
117c
118c     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
119c
120      DO l = llm -1 , 2 , -1
121c
122        DO ij = 1, ngrid
123        dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
124        alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
125        beta (ij,l)  =   p(ij,l  ) / dellta   
126        ENDDO
127c
128      ENDDO
129c
130c  ***********************************************************************
131c     .....  Calcul de pk pour la couche 1 , pres du sol  ....
132c
133      DO   ij   = 1, ngrid
134       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  /
135     *    (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
136      ENDDO
137c
138c    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
139c
140      DO l = 2, llm
141        DO   ij   = 1, ngrid
142         pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
143        ENDDO
144      ENDDO
145c
146c
147      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
148      CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
149     
150
151      RETURN
152      END
Note: See TracBrowser for help on using the repository browser.