source: trunk/LMDZ.COMMON/libf/dyn3d_common/exner_milieu_m.F90 @ 3493

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