source: trunk/LMDZ.GENERIC/libf/dyn3d/exner_hyb.F @ 773

Last change on this file since 773 was 135, checked in by aslmd, 14 years ago

CHANGEMENT ARBORESCENCE ETAPE 2 -- NON COMPLET

File size: 2.9 KB
Line 
1      SUBROUTINE  exner_hyb ( ngrid, ps, p,beta, pks, pk, pkf )
2c
3c     Auteurs :  F. Forget , Y. Wanherdrick
4c P.Le Van  , Fr. Hourdin  .
5c    ..........
6c
7c    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
8c    .... beta, pks,pk,pkf   sont des argum.de sortie au sous-prog ...
9c
10c   ************************************************************************
11c    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
12c    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
13c    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
14c   ************************************************************************
15c    .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
16c    la pression et la fonction d'Exner  au  sol  .
17c
18c     WARNING : CECI est une version speciale de exner_hyb originale
19c               Utilis‰ dans la version martienne pour pouvoir
20c               tourner avec des coordonn‰es verticales complexe
21c              => Il ne verifie PAS la condition la proportionalit‰ en
22c              ‰nergie totale/ interne / potentielle (F.Forget 2001)
23c    ( voir note de Fr.Hourdin )  ,
24c
25      IMPLICIT NONE
26c
27#include "dimensions.h"
28#include "paramet.h"
29#include "comconst.h"
30#include "comgeom.h"
31#include "comvert.h"
32#include "serre.h"
33
34      INTEGER  ngrid
35      REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
36      REAL ps(ngrid),pks(ngrid), beta(ngrid,llm)
37
38c    .... variables locales   ...
39
40      INTEGER l, ij
41      REAL dum1
42
43      REAL ppn(iim),pps(iim)
44      REAL xpn, xps
45      REAL SSUM
46      EXTERNAL filtreg, SSUM
47     
48c     -------------
49c     Calcul de pks
50c     -------------
51   
52      DO   ij  = 1, ngrid
53        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
54      ENDDO
55
56      DO  ij   = 1, iim
57        ppn(ij) = aire(   ij   ) * pks(  ij     )
58        pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
59      ENDDO
60      xpn      = SSUM(iim,ppn,1) /apoln
61      xps      = SSUM(iim,pps,1) /apols
62
63      DO ij   = 1, iip1
64        pks(   ij     )  =  xpn
65        pks( ij+ip1jm )  =  xps
66      ENDDO
67c
68c
69c    .... Calcul de pk  pour la couche l
70c    --------------------------------------------
71c
72      dum1 = cpp * (2*preff)**(-kappa)
73      DO l = 1, llm-1
74        DO   ij   = 1, ngrid
75         pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
76        ENDDO
77      ENDDO
78
79c    .... Calcul de pk  pour la couche l = llm ..
80c    (on met la meme distance (en log pression)  entre Pk(llm)
81c    et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
82
83      DO   ij   = 1, ngrid
84         pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
85      ENDDO
86
87
88c    calcul de pkf
89c    -------------
90      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
91      CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
92     
93c    EST-CE UTILE ?? : calcul de beta
94c    --------------------------------
95      DO l = 2, llm
96        DO   ij   = 1, ngrid
97          beta(ij,l) = pk(ij,l) / pk(ij,l-1)   
98        ENDDO
99      ENDDO
100
101      RETURN
102      END
Note: See TracBrowser for help on using the repository browser.