source: LMDZ5/trunk/libf/dyn3dmem/exner_hyb_loc_m.F90 @ 2021

Last change on this file since 2021 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
File size: 5.5 KB
Line 
1module exner_hyb_loc_m
2
3  IMPLICIT NONE
4
5contains
6
7  SUBROUTINE  exner_hyb_loc(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    USE mod_filtreg_p
36    USE write_field_loc
37    !
38    include "dimensions.h"
39    include "paramet.h"
40    include "comconst.h"
41    include "comgeom.h"
42    include "comvert.h"
43    include "serre.h"
44
45    INTEGER  ngrid
46    REAL p(ijb_u:ije_u,llmp1),pk(ijb_u:ije_u,llm)
47    REAL, optional:: pkf(ijb_u:ije_u,llm)
48    REAL ps(ijb_u:ije_u),pks(ijb_u:ije_u)
49    REAL alpha(ijb_u:ije_u,llm),beta(ijb_u:ije_u,llm)
50
51    !    .... variables locales   ...
52
53    INTEGER l, ij
54    REAL unpl2k,dellta
55
56    INTEGER ije,ijb,jje,jjb
57    logical,save :: firstcall=.true.
58    !$OMP THREADPRIVATE(firstcall)
59    character(len=*),parameter :: modname="exner_hyb_loc"
60    !
61    !$OMP BARRIER           
62
63    ! Sanity check
64    if (firstcall) then
65       ! sanity checks for Shallow Water case (1 vertical layer)
66       if (llm.eq.1) then
67          if (kappa.ne.1) then
68             call abort_gcm(modname, &
69                  "kappa!=1 , but running in Shallow Water mode!!",42)
70          endif
71          if (cpp.ne.r) then
72             call abort_gcm(modname, &
73                  "cpp!=r , but running in Shallow Water mode!!",42)
74          endif
75       endif ! of if (llm.eq.1)
76
77       firstcall=.false.
78    endif ! of if (firstcall)
79
80    !$OMP BARRIER
81
82    ! Specific behaviour for Shallow Water (1 vertical layer) case:
83    if (llm.eq.1) then
84
85       ! Compute pks(:),pk(:),pkf(:)
86       ijb=ij_begin
87       ije=ij_end
88       !$OMP DO SCHEDULE(STATIC)
89       DO ij=ijb, ije
90          pks(ij) = (cpp/preff) * ps(ij)
91          pk(ij,1) = .5*pks(ij)
92          if (present(pkf)) pkf(ij,1)=pk(ij,1)
93       ENDDO
94       !$OMP ENDDO
95
96       !$OMP BARRIER
97       if (present(pkf)) then
98          jjb=jj_begin
99          jje=jj_end
100          CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm, &
101               2, 1, .TRUE., 1 )
102       end if
103
104       ! our work is done, exit routine
105       return
106    endif ! of if (llm.eq.1)
107
108    ! General case:
109
110    unpl2k    = 1.+ 2.* kappa
111
112    !     -------------
113    !     Calcul de pks
114    !     -------------
115
116    ijb=ij_begin
117    ije=ij_end
118
119    !$OMP DO SCHEDULE(STATIC)
120    DO   ij  = ijb, ije
121       pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
122    ENDDO
123    !$OMP ENDDO
124    ! Synchro OPENMP ici
125
126    !$OMP BARRIER
127    !
128    !
129    !    .... Calcul des coeff. alpha et beta  pour la couche l = llm ..
130    !
131    !$OMP DO SCHEDULE(STATIC)
132    DO     ij      = ijb,ije
133       alpha(ij,llm) = 0.
134       beta (ij,llm) = 1./ unpl2k
135    ENDDO
136    !$OMP ENDDO NOWAIT
137    !
138    !     ... Calcul des coeff. alpha et beta  pour l = llm-1  a l = 2 ...
139    !
140    DO l = llm -1 , 2 , -1
141       !
142       !$OMP DO SCHEDULE(STATIC)
143       DO ij = ijb, ije
144          dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
145          alpha(ij,l)  = - p(ij,l+1) / dellta * alpha(ij,l+1)
146          beta (ij,l)  =   p(ij,l  ) / dellta   
147       ENDDO
148       !$OMP ENDDO NOWAIT
149    ENDDO
150
151    !  ***********************************************************************
152    !     .....  Calcul de pk pour la couche 1 , pres du sol  ....
153    !
154    !$OMP DO SCHEDULE(STATIC)
155    DO   ij   = ijb, ije
156       pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) )  / &
157            (  p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
158    ENDDO
159    !$OMP ENDDO NOWAIT
160    !
161    !    ..... Calcul de pk(ij,l) , pour l = 2 a l = llm  ........
162    !
163    DO l = 2, llm
164       !$OMP DO SCHEDULE(STATIC)
165       DO   ij   = ijb, ije
166          pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
167       ENDDO
168       !$OMP ENDDO NOWAIT       
169    ENDDO
170
171    if (present(pkf)) then
172       !    calcul de pkf
173
174       DO l = 1, llm
175          !$OMP DO SCHEDULE(STATIC)
176          DO   ij   = ijb, ije
177             pkf(ij,l)=pk(ij,l)
178          ENDDO
179          !$OMP ENDDO NOWAIT             
180       ENDDO
181
182       !$OMP BARRIER
183
184       jjb=jj_begin
185       jje=jj_end
186#ifdef DEBUG_IO   
187       call WriteField_u('pkf',pkf)
188#endif
189       CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm, &
190            2, 1, .TRUE., 1 )
191#ifdef DEBUG_IO   
192       call WriteField_u('pkf',pkf)
193#endif     
194    end if
195
196  END SUBROUTINE exner_hyb_loc
197
198end module exner_hyb_loc_m
Note: See TracBrowser for help on using the repository browser.