source: LMDZ5/trunk/libf/dyn3dmem/exner_milieu_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: 4.5 KB
Line 
1module exner_milieu_loc_m
2
3  IMPLICIT NONE
4
5contains
6
7  SUBROUTINE  exner_milieu_loc ( 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 parallel_lmdz
32    USE mod_filtreg_p
33    !
34    include "dimensions.h"
35    include "paramet.h"
36    include "comconst.h"
37    include "comgeom.h"
38    include "comvert.h"
39    include "serre.h"
40
41    INTEGER  ngrid
42    REAL p(ijb_u:ije_u,llmp1),pk(ijb_u:ije_u,llm)
43    REAL, optional:: pkf(ijb_u:ije_u,llm)
44    REAL ps(ijb_u:ije_u),pks(ijb_u:ije_u)
45
46    !    .... variables locales   ...
47
48    INTEGER l, ij
49    REAL dum1
50
51    INTEGER ije,ijb,jje,jjb
52    logical,save :: firstcall=.true.
53    !$OMP THREADPRIVATE(firstcall)
54    character(len=*),parameter :: modname="exner_milieu_loc"
55
56    ! Sanity check
57    if (firstcall) then
58       ! sanity checks for Shallow Water case (1 vertical layer)
59       if (llm.eq.1) then
60          if (kappa.ne.1) then
61             call abort_gcm(modname, &
62                  "kappa!=1 , but running in Shallow Water mode!!",42)
63          endif
64          if (cpp.ne.r) then
65             call abort_gcm(modname, &
66                  "cpp!=r , but running in Shallow Water mode!!",42)
67          endif
68       endif ! of if (llm.eq.1)
69
70       firstcall=.false.
71    endif ! of if (firstcall)
72
73    !$OMP BARRIER
74
75    ! Specific behaviour for Shallow Water (1 vertical layer) case:
76    if (llm.eq.1) then
77
78       ! Compute pks(:),pk(:),pkf(:)
79       ijb=ij_begin
80       ije=ij_end
81       !$OMP DO SCHEDULE(STATIC)
82       DO ij=ijb, ije
83          pks(ij) = (cpp/preff) * ps(ij)
84          pk(ij,1) = .5*pks(ij)
85          if (present(pkf)) pkf(ij,1)=pk(ij,1)
86       ENDDO
87       !$OMP ENDDO
88
89       !$OMP BARRIER
90       if (present(pkf)) then
91          jjb=jj_begin
92          jje=jj_end
93          CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm, &
94               2, 1, .TRUE., 1 )
95       end if
96
97       ! our work is done, exit routine
98       return
99    endif ! of if (llm.eq.1)
100
101    ! General case:
102
103    !     -------------
104    !     Calcul de pks
105    !     -------------
106
107    ijb=ij_begin
108    ije=ij_end
109
110    !$OMP DO SCHEDULE(STATIC)
111    DO   ij  = ijb, ije
112       pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
113    ENDDO
114    !$OMP ENDDO
115    ! Synchro OPENMP ici
116
117    !$OMP BARRIER
118    !
119    !
120    !    .... Calcul de pk  pour la couche l
121    !    --------------------------------------------
122    !
123    dum1 = cpp * (2*preff)**(-kappa)
124    DO l = 1, llm-1
125       !$OMP DO SCHEDULE(STATIC)
126       DO   ij   = ijb, ije
127          pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
128       ENDDO
129       !$OMP ENDDO NOWAIT
130    ENDDO
131
132    !    .... Calcul de pk  pour la couche l = llm ..
133    !    (on met la meme distance (en log pression)  entre Pk(llm)
134    !    et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
135
136    !$OMP DO SCHEDULE(STATIC)
137    DO   ij   = ijb, ije
138       pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
139    ENDDO
140    !$OMP ENDDO NOWAIT       
141
142    if (present(pkf)) then
143       !    calcul de pkf
144
145       DO l = 1, llm
146          !$OMP DO SCHEDULE(STATIC)
147          DO   ij   = ijb, ije
148             pkf(ij,l)=pk(ij,l)
149          ENDDO
150          !$OMP ENDDO NOWAIT
151       ENDDO
152
153       !$OMP BARRIER
154
155       jjb=jj_begin
156       jje=jj_end
157       CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm, &
158            2, 1, .TRUE., 1 )
159    end if
160
161  END SUBROUTINE exner_milieu_loc
162
163end module exner_milieu_loc_m
Note: See TracBrowser for help on using the repository browser.