source: LMDZ6/trunk/libf/dyn3d_common/exner_milieu_m.f90 @ 5359

Last change on this file since 5359 was 5285, checked in by abarral, 7 weeks ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

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