source: LMDZ6/trunk/libf/dyn3d_common/exner_hyb_m.f90 @ 5300

Last change on this file since 5300 was 5285, checked in by abarral, 4 days 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.3 KB
Line 
1module exner_hyb_m
2
3  USE comgeom_mod_h
4    IMPLICIT NONE
5
6contains
7
8  SUBROUTINE  exner_hyb ( ngrid, ps, p, pks, pk, pkf )
9
10    !     Auteurs :  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    !                                 -------- z
25    !    A partir des relations  ( 1 ) p*dz(pk) = kappa *pk*dz(p)      et
26    !                            ( 2 ) pk(l) = alpha(l)+ beta(l)*pk(l-1)
27    !    ( voir note de Fr.Hourdin )  ,
28    !
29    !    on determine successivement , du haut vers le bas des couches, les
30    !    coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2),
31    !    puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches,
32    !     pk(ij,l)  donne  par la relation (2),  pour l = 2 a l = llm .
33    !
34    !
35    !
36    USE comconst_mod, ONLY: jmp1, cpp, kappa, r
37    USE comvert_mod, ONLY: preff
38
39    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
40USE paramet_mod_h
41IMPLICIT NONE
42
43
44
45
46    INTEGER  ngrid
47    REAL p(ngrid,llmp1),pk(ngrid,llm)
48    real, optional:: pkf(ngrid,llm)
49    REAL ps(ngrid),pks(ngrid), alpha(ngrid,llm),beta(ngrid,llm)
50
51    !    .... variables locales   ...
52
53    INTEGER l, ij
54    REAL unpl2k,dellta
55
56    logical,save :: firstcall=.true.
57    character(len=*),parameter :: modname="exner_hyb"
58
59    ! Sanity check
60    if (firstcall) then
61       ! sanity checks for Shallow Water case (1 vertical layer)
62       if (llm.eq.1) then
63          if (kappa.ne.1) then
64             call abort_gcm(modname, &
65                  "kappa!=1 , but running in Shallow Water mode!!",42)
66          endif
67          if (cpp.ne.r) then
68             call abort_gcm(modname, &
69                  "cpp!=r , but running in Shallow Water mode!!",42)
70          endif
71       endif ! of if (llm.eq.1)
72
73       firstcall=.false.
74    endif ! of if (firstcall)
75
76    ! Specific behaviour for Shallow Water (1 vertical layer) case:
77    if (llm.eq.1) then
78
79       ! Compute pks(:),pk(:),pkf(:)
80
81       DO   ij  = 1, ngrid
82          pks(ij) = (cpp/preff) * ps(ij)
83          pk(ij,1) = .5*pks(ij)
84       ENDDO
85
86       if (present(pkf)) then
87          pkf = pk
88          CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
89       end if
90
91       ! our work is done, exit routine
92       return
93    endif ! of if (llm.eq.1)
94
95    ! General case:
96
97    unpl2k    = 1.+ 2.* kappa
98
99    !     -------------
100    !     Calcul de pks
101    !     -------------
102
103    DO   ij  = 1, ngrid
104       pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
105    ENDDO
106
107    !    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
108    !
109    DO     ij      = 1, ngrid
110       alpha(ij,llm) = 0.
111       beta (ij,llm) = 1./ unpl2k
112    ENDDO
113    !
114    !     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
115    !
116    DO l = llm -1 , 2 , -1
117       !
118       DO ij = 1, ngrid
119          dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
120          alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
121          beta (ij,l)  =   p(ij,l  ) / dellta   
122       ENDDO
123    ENDDO
124
125    !  ***********************************************************************
126    !     .....  Calcul de pk pour la couche 1 , pres du sol  ....
127    !
128    DO   ij   = 1, ngrid
129       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  / &
130            (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
131    ENDDO
132    !
133    !    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
134    !
135    DO l = 2, llm
136       DO   ij   = 1, ngrid
137          pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
138       ENDDO
139    ENDDO
140
141    if (present(pkf)) then
142       !    calcul de pkf
143       pkf = pk
144       CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
145    end if
146
147  END SUBROUTINE exner_hyb
148
149end module exner_hyb_m
Note: See TracBrowser for help on using the repository browser.