source: trunk/LMDZ.COMMON/libf/dyn3d_common/exner_hyb_m.F90 @ 1422

Last change on this file since 1422 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: 4.3 KB
Line 
1module exner_hyb_m
2
3  USE comvert_mod, ONLY: preff
4  USE comconst_mod, ONLY: jmp1,kappa,cpp,r,pi
5
6  IMPLICIT NONE
7
8contains
9
10  SUBROUTINE  exner_hyb ( ngrid, ps, p, pks, pk, pkf )
11
12    !     Auteurs :  P.Le Van  , Fr. Hourdin  .
13    !    ..........
14    !
15    !    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
16    !    ....  pks,pk,pkf   sont des argum.de sortie au sous-prog ...
17    !
18    !   ************************************************************************
19    !    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
20    !    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
21    !    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
22    !   ************************************************************************
23    !  .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
24    !    la pression et la fonction d'Exner  au  sol  .
25    !
26    !                                 -------- z
27    !    A partir des relations  ( 1 ) p*dz(pk) = kappa *pk*dz(p)      et
28    !                            ( 2 ) pk(l) = alpha(l)+ beta(l)*pk(l-1)
29    !    ( voir note de Fr.Hourdin )  ,
30    !
31    !    on determine successivement , du haut vers le bas des couches, les
32    !    coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2),
33    !    puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches, 
34    !     pk(ij,l)  donne  par la relation (2),  pour l = 2 a l = llm .
35    !
36    !
37    !
38    include "dimensions.h"
39    include "paramet.h"
40    include "comgeom.h"
41
42    INTEGER  ngrid
43    REAL p(ngrid,llmp1),pk(ngrid,llm)
44    real, optional:: pkf(ngrid,llm)
45    REAL ps(ngrid),pks(ngrid), alpha(ngrid,llm),beta(ngrid,llm)
46
47    !    .... variables locales   ...
48
49    INTEGER l, ij
50    REAL unpl2k,dellta
51
52    logical,save :: firstcall=.true.
53    character(len=*),parameter :: modname="exner_hyb"
54
55    ! Sanity check
56    if (firstcall) then
57       ! sanity checks for Shallow Water case (1 vertical layer)
58       if (llm.eq.1) then
59          if (kappa.ne.1) then
60             call abort_gcm(modname, &
61                  "kappa!=1 , but running in Shallow Water mode!!",42)
62          endif
63          if (cpp.ne.r) then
64             call abort_gcm(modname, &
65                  "cpp!=r , but running in Shallow Water mode!!",42)
66          endif
67       endif ! of if (llm.eq.1)
68
69       firstcall=.false.
70    endif ! of if (firstcall)
71
72    ! Specific behaviour for Shallow Water (1 vertical layer) case:
73    if (llm.eq.1) then
74
75       ! Compute pks(:),pk(:),pkf(:)
76
77       DO   ij  = 1, ngrid
78          pks(ij) = (cpp/preff) * ps(ij)
79          pk(ij,1) = .5*pks(ij)
80       ENDDO
81
82       if (present(pkf)) then
83          pkf = pk
84          CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
85       end if
86
87       ! our work is done, exit routine
88       return
89    endif ! of if (llm.eq.1)
90
91    ! General case:
92
93    unpl2k    = 1.+ 2.* kappa
94
95    !     -------------
96    !     Calcul de pks
97    !     -------------
98
99    DO   ij  = 1, ngrid
100       pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
101    ENDDO
102
103    !    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
104    !
105    DO     ij      = 1, ngrid
106       alpha(ij,llm) = 0.
107       beta (ij,llm) = 1./ unpl2k
108    ENDDO
109    !
110    !     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
111    !
112    DO l = llm -1 , 2 , -1
113       !
114       DO ij = 1, ngrid
115          dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
116          alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
117          beta (ij,l)  =   p(ij,l  ) / dellta   
118       ENDDO
119    ENDDO
120
121    !  ***********************************************************************
122    !     .....  Calcul de pk pour la couche 1 , pres du sol  ....
123    !
124    DO   ij   = 1, ngrid
125       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  / &
126            (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
127    ENDDO
128    !
129    !    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
130    !
131    DO l = 2, llm
132       DO   ij   = 1, ngrid
133          pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
134       ENDDO
135    ENDDO
136
137    if (present(pkf)) then
138       !    calcul de pkf
139       pkf = pk
140       CALL filtreg ( pkf, jmp1, llm, 2, 1, .TRUE., 1 )
141    end if
142
143  END SUBROUTINE exner_hyb
144
145end module exner_hyb_m
146
Note: See TracBrowser for help on using the repository browser.