source: LMDZ5/branches/testing/libf/dyn3d_common/exner_milieu.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
File size: 4.0 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      logical,save :: firstcall=.true.
51      character(len=*),parameter :: modname="exner_milieu"
52
53      ! Sanity check
54      if (firstcall) then
55        ! sanity checks for Shallow Water case (1 vertical layer)
56        if (llm.eq.1) then
57          if (kappa.ne.1) then
58            call abort_gcm(modname,
59     &      "kappa!=1 , but running in Shallow Water mode!!",42)
60          endif
61          if (cpp.ne.r) then
62            call abort_gcm(modname,
63     &      "cpp!=r , but running in Shallow Water mode!!",42)
64          endif
65        endif ! of if (llm.eq.1)
66
67        firstcall=.false.
68      endif ! of if (firstcall)
69
70!!!! Specific behaviour for Shallow Water (1 vertical layer) case:
71      if (llm.eq.1) then
72     
73        ! Compute pks(:),pk(:),pkf(:)
74       
75        DO   ij  = 1, ngrid
76          pks(ij) = (cpp/preff) * ps(ij)
77          pk(ij,1) = .5*pks(ij)
78        ENDDO
79       
80        CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
81        CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
82       
83        ! our work is done, exit routine
84        return
85
86      endif ! of if (llm.eq.1)
87
88!!!! General case:
89
90c     -------------
91c     Calcul de pks
92c     -------------
93   
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 de pk  pour la couche l
112c    --------------------------------------------
113c
114      dum1 = cpp * (2*preff)**(-kappa)
115      DO l = 1, llm-1
116        DO   ij   = 1, ngrid
117         pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
118        ENDDO
119      ENDDO
120
121c    .... Calcul de pk  pour la couche l = llm ..
122c    (on met la meme distance (en log pression)  entre Pk(llm)
123c    et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
124
125      DO   ij   = 1, ngrid
126         pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
127      ENDDO
128
129
130c    calcul de pkf
131c    -------------
132      CALL SCOPY   ( ngrid * llm, pk, 1, pkf, 1 )
133      CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
134     
135c    EST-CE UTILE ?? : calcul de beta
136c    --------------------------------
137      DO l = 2, llm
138        DO   ij   = 1, ngrid
139          beta(ij,l) = pk(ij,l) / pk(ij,l-1)   
140        ENDDO
141      ENDDO
142
143      RETURN
144      END
Note: See TracBrowser for help on using the repository browser.