source: trunk/libf/dyn3d/exner_milieu.F @ 124

Last change on this file since 124 was 124, checked in by emillour, 14 years ago

EM: suite mise au point discretisation verticale et quelques corrections de bugs dans le version de reference parallele.

File size: 3.7 KB
Line 
1!
2! $Id $
3!
4      SUBROUTINE  exner_milieu ( ngrid, ps, p,beta, pks, pk, pkf )
5c
6c     Auteurs :  F. Forget , Y. Wanherdrick
7c P.Le Van  , Fr. Hourdin  .
8c    ..........
9c
10c    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
11c    .... beta, pks,pk,pkf   sont des argum.de sortie au sous-prog ...
12c
13c   ************************************************************************
14c    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
15c    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
16c    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
17c   ************************************************************************
18c    .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
19c    la pression et la fonction d'Exner  au  sol  .
20c
21c     WARNING : CECI est une version speciale de exner_hyb originale
22c               Utilise dans la version martienne pour pouvoir
23c               tourner avec des coordonnees verticales complexe
24c              => Il ne verifie PAS la condition la proportionalite en
25c              energie totale/ interne / potentielle (F.Forget 2001)
26c    ( voir note de Fr.Hourdin )  ,
27c
28      IMPLICIT NONE
29c
30#include "dimensions.h"
31#include "paramet.h"
32#include "comconst.h"
33#include "comgeom.h"
34#include "comvert.h"
35#include "serre.h"
36
37      INTEGER  ngrid
38      REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
39      REAL ps(ngrid),pks(ngrid), beta(ngrid,llm)
40
41c    .... variables locales   ...
42
43      INTEGER l, ij
44      REAL dum1
45
46      REAL ppn(iim),pps(iim)
47      REAL xpn, xps
48      REAL SSUM
49      EXTERNAL SSUM
50
51      if (llm.eq.1) then
52        ! Specific behaviour for Shallow Water (1 vertical layer) case
53     
54        ! Sanity checks
55        if (kappa.ne.1) then
56          call abort_gcm("exner_hyb",
57     &    "kappa!=1 , but running in Shallow Water mode!!",42)
58        endif
59        if (cpp.ne.r) then
60        call abort_gcm("exner_hyb",
61     &    "cpp!=r , but running in Shallow Water mode!!",42)
62        endif
63       
64        ! Compute pks(:),pk(:),pkf(:)
65       
66        DO   ij  = 1, ngrid
67          pks(ij) = (cpp/preff) * ps(ij)
68          pk(ij,1) = .5*pks(ij)
69        ENDDO
70       
71        CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
72        CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
73       
74        ! our work is done, exit routine
75        return
76      endif ! of if (llm.eq.1)
77
78     
79c     -------------
80c     Calcul de pks
81c     -------------
82   
83      DO   ij  = 1, ngrid
84        pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
85      ENDDO
86
87      DO  ij   = 1, iim
88        ppn(ij) = aire(   ij   ) * pks(  ij     )
89        pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
90      ENDDO
91      xpn      = SSUM(iim,ppn,1) /apoln
92      xps      = SSUM(iim,pps,1) /apols
93
94      DO ij   = 1, iip1
95        pks(   ij     )  =  xpn
96        pks( ij+ip1jm )  =  xps
97      ENDDO
98c
99c
100c    .... Calcul de pk  pour la couche l
101c    --------------------------------------------
102c
103      dum1 = cpp * (2*preff)**(-kappa)
104      DO l = 1, llm-1
105        DO   ij   = 1, ngrid
106         pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
107        ENDDO
108      ENDDO
109
110c    .... Calcul de pk  pour la couche l = llm ..
111c    (on met la meme distance (en log pression)  entre Pk(llm)
112c    et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
113
114      DO   ij   = 1, ngrid
115         pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
116      ENDDO
117
118
119c    calcul de pkf
120c    -------------
121      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
122      CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
123     
124c    EST-CE UTILE ?? : calcul de beta
125c    --------------------------------
126      DO l = 2, llm
127        DO   ij   = 1, ngrid
128          beta(ij,l) = pk(ij,l) / pk(ij,l-1)   
129        ENDDO
130      ENDDO
131
132      RETURN
133      END
Note: See TracBrowser for help on using the repository browser.