source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/exner_milieu_m.F90 @ 5136

Last change on this file since 5136 was 5136, checked in by abarral, 8 weeks ago

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