source: trunk/LMDZ.PLUTO.old/libf/dyn3d/exner_hyb.F @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

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      DO   ij  = 1, ngrid
52        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
53      ENDDO
54
55      DO  ij   = 1, iim
56        ppn(ij) = aire(   ij   ) * pks(  ij     )
57        pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
58      ENDDO
59      xpn      = SSUM(iim,ppn,1) /apoln
60      xps      = SSUM(iim,pps,1) /apols
61
62      DO ij   = 1, iip1
63        pks(   ij     )  =  xpn
64        pks( ij+ip1jm )  =  xps
65      ENDDO
66c
67c
68c    .... Calcul de pk  pour la couche l
69c    --------------------------------------------
70c
71      dum1 = cpp * (2*preff)**(-kappa)
72      DO l = 1, llm-1
73        DO   ij   = 1, ngrid
74         pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
75        ENDDO
76      ENDDO
77
78c    .... Calcul de pk  pour la couche l = llm ..
79c    (on met la meme distance (en log pression)  entre Pk(llm)
80c    et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
81
82      DO   ij   = 1, ngrid
83         pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
84      ENDDO
85
86
87c    calcul de pkf
88c    -------------
89      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
90      CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
91     
92c    EST-CE UTILE ?? : calcul de beta
93c    --------------------------------
94      DO l = 2, llm
95        DO   ij   = 1, ngrid
96          beta(ij,l) = pk(ij,l) / pk(ij,l-1)   
97        ENDDO
98      ENDDO
99
100      RETURN
101      END
Note: See TracBrowser for help on using the repository browser.