source: trunk/LMDZ.MARS/libf/dyn3d/exnerF @ 1766

Last change on this file since 1766 was 1422, checked in by milmd, 10 years ago

In GENERIC, MARS and COMMON models replace some include files by modules (usefull for decoupling physics with dynamics).

File size: 2.8 KB
Line 
1      SUBROUTINE  exner ( ngrid, ps, p, 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    .... 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      IMPLICIT NONE
29c
30#include "dimensions.h"
31#include "paramet.h"
32
33      INTEGER  ngrid
34      REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
35      REAL ps(ngrid),pks(ngrid)
36      INTEGER l, ij
37      REAL alpha(ngrid,llm),beta(ngrid,llm),unpl2k,delta
38      EXTERNAL filtreg
39c
40      unpl2k    = 1.+ 2.* kappa
41c
42      DO   ij  = 1, ngrid
43       pks(ij) = cpp * (ps(ij)/preff) ** kappa
44      ENDDO
45c
46c    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
47c
48      DO     ij      = 1, ngrid
49       alpha(ij,llm) = 0.
50       beta (ij,llm) = 1./ unpl2k
51      ENDDO
52c
53c     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
54c
55      DO l = llm -1 , 2 , -1
56c
57        DO ij = 1, ngrid
58        delta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
59        alpha(ij,l)  = - p(ij,l+1) / delta * alpha(ij,l+1)
60        beta (ij,l)  =   p(ij,l  ) / delta   
61        ENDDO
62c
63      ENDDO
64c
65c  ***********************************************************************
66c     .....  Calcul de pk pour la couche 1 , pres du sol  ....
67c
68      DO   ij   = 1, ngrid
69       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  /
70     *    (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
71      ENDDO
72c
73c    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
74c
75      DO l = 2, llm
76        DO   ij   = 1, ngrid
77         pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
78        ENDDO
79      ENDDO
80c
81c
82      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
83      CALL filtreg ( pkf, jmp1, llm, 2, 1, .true., 1)
84
85      RETURN
86      END
Note: See TracBrowser for help on using the repository browser.