source: LMDZ5/branches/AI-cosp/libf/dyn3dpar/exner_hyb_p_m.F90

Last change on this file was 2021, checked in by lguez, 10 years ago

Removed unused variables pks, pk, pkf from main program unit gcm.

Encapsulated procedures exner_hyb, exner_hyb_p, exner_hyb_loc,
exner_milieu, exner_milieu_p and exner_milieu_loc into
modules. (Compulsory to allow optional arguments.)

In the procedures exner_hyb, exner_hyb_p, exner_hyb_loc, donwgraded
arguments alpha and beta to local variables. In exner_milieu,
exner_milieu_p and exner_milieu_loc, removed beta altogether. In the
six procedures exner_*, made pkf an optional argument. Made some
cosmetic modifications in order to keep the six procedures exner_* as
close as possible.

In the six procedures exner_*, removed the averaging of pks at the
poles: this is not useful because ps is already the same at all
longitudes at the poles. This modification changes the results of the
program. Motivation: had to do this for exner_hyb because we call it
from test_disvert with a few surface pressure values.

In all the procedures calling exner_*, removed the variables alpha and
beta. Also removed variables alpha and beta from module leapfrog_mod
and from module call_calfis_mod.

Removed actual argument pkf in call to exner_hyb* and exner_milieu*
from guide_interp, guide_main, iniacademic and iniacademic_loc (pkf
was not used in those procedures).

Argument workvar of startget_dyn is used only if varname is tpot or

  1. When varname is tpot or q, the actual argument associated to

workvar in etat0_netcdf is not y. So y in etat0_netcdf is a
place-holder, never used. So we remove optional argument y in the
calls to exner_hyb and exner_milieu from etat0_netcdf.

Created procedure test_disvert, called only by etat0_netcdf. This
procedure tests the order of pressure values at half-levels and full
levels.

  • 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: 5.2 KB
Line 
1module exner_hyb_p_m
2
3  IMPLICIT NONE
4
5contains
6
7  SUBROUTINE  exner_hyb_p ( ngrid, ps, p, pks, pk, pkf )
8
9    !     Auteurs :  P.Le Van  , Fr. Hourdin  .
10    !    ..........
11    !
12    !    ....  ngrid, ps,p             sont des argum.d'entree  au sous-prog ...
13    !    ....  pks,pk,pkf   sont des argum.de sortie au sous-prog ...
14    !
15    !   ************************************************************************
16    !    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
17    !    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
18    !    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
19    !   ************************************************************************
20    !  .. N.B : Au sommet de l'atmosphere,  p(llm+1) = 0. , et ps et pks sont
21    !    la pression et la fonction d'Exner  au  sol  .
22    !
23    !                                 -------- z
24    !    A partir des relations  ( 1 ) p*dz(pk) = kappa *pk*dz(p)      et
25    !                            ( 2 ) pk(l) = alpha(l)+ beta(l)*pk(l-1)
26    !    ( voir note de Fr.Hourdin )  ,
27    !
28    !    on determine successivement , du haut vers le bas des couches, les
29    !    coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2),
30    !    puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches, 
31    !     pk(ij,l)  donne  par la relation (2),  pour l = 2 a l = llm .
32    !
33    !
34    USE parallel_lmdz
35    !
36    include "dimensions.h"
37    include "paramet.h"
38    include "comconst.h"
39    include "comgeom.h"
40    include "comvert.h"
41    include "serre.h"
42
43    INTEGER  ngrid
44    REAL p(ngrid,llmp1),pk(ngrid,llm)
45    REAL, optional:: pkf(ngrid,llm)
46    REAL ps(ngrid),pks(ngrid)
47    REAL alpha(ngrid,llm),beta(ngrid,llm)
48
49    !    .... variables locales   ...
50
51    INTEGER l, ij
52    REAL unpl2k,dellta
53
54    INTEGER ije,ijb,jje,jjb
55    logical,save :: firstcall=.true.
56    !$OMP THREADPRIVATE(firstcall)
57    character(len=*),parameter :: modname="exner_hyb_p"
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    !$OMP BARRIER
77
78    ! Specific behaviour for Shallow Water (1 vertical layer) case:
79    if (llm.eq.1) then
80
81       ! Compute pks(:),pk(:),pkf(:)
82       ijb=ij_begin
83       ije=ij_end
84       !$OMP DO SCHEDULE(STATIC)
85       DO ij=ijb, ije
86          pks(ij) = (cpp/preff) * ps(ij)
87          pk(ij,1) = .5*pks(ij)
88          if (present(pkf)) pkf(ij,1)=pk(ij,1)
89       ENDDO
90       !$OMP ENDDO
91
92       !$OMP BARRIER
93       if (present(pkf)) then
94          jjb=jj_begin
95          jje=jj_end
96          CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
97       end if
98
99       ! our work is done, exit routine
100       return
101    endif ! of if (llm.eq.1)
102
103    ! General case:
104
105    unpl2k    = 1.+ 2.* kappa
106
107    !     -------------
108    !     Calcul de pks
109    !     -------------
110
111    ijb=ij_begin
112    ije=ij_end
113
114    !$OMP DO SCHEDULE(STATIC)
115    DO   ij  = ijb, ije
116       pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
117    ENDDO
118    !$OMP ENDDO
119    ! Synchro OPENMP ici
120
121    !$OMP BARRIER
122    !
123    !
124    !    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
125    !
126    !$OMP DO SCHEDULE(STATIC)
127    DO     ij      = ijb,ije
128       alpha(ij,llm) = 0.
129       beta (ij,llm) = 1./ unpl2k
130    ENDDO
131    !$OMP ENDDO NOWAIT
132    !
133    !     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
134    !
135    DO l = llm -1 , 2 , -1
136       !
137       !$OMP DO SCHEDULE(STATIC)
138       DO ij = ijb, ije
139          dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
140          alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
141          beta (ij,l)  =   p(ij,l  ) / dellta   
142       ENDDO
143       !$OMP ENDDO NOWAIT
144    ENDDO
145
146    !  ***********************************************************************
147    !     .....  Calcul de pk pour la couche 1 , pres du sol  ....
148    !
149    !$OMP DO SCHEDULE(STATIC)
150    DO   ij   = ijb, ije
151       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  / &
152            (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
153    ENDDO
154    !$OMP ENDDO NOWAIT
155    !
156    !    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
157    !
158    DO l = 2, llm
159       !$OMP DO SCHEDULE(STATIC)
160       DO   ij   = ijb, ije
161          pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
162       ENDDO
163       !$OMP ENDDO NOWAIT       
164    ENDDO
165
166    if (present(pkf)) then
167       !    calcul de pkf
168
169       DO l = 1, llm
170          !$OMP DO SCHEDULE(STATIC)
171          DO   ij   = ijb, ije
172             pkf(ij,l)=pk(ij,l)
173          ENDDO
174          !$OMP ENDDO NOWAIT             
175       ENDDO
176
177       !$OMP BARRIER
178
179       jjb=jj_begin
180       jje=jj_end
181       CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .TRUE., 1 )
182    end if
183
184  END SUBROUTINE exner_hyb_p
185
186end module exner_hyb_p_m
Note: See TracBrowser for help on using the repository browser.