LMDZ
yomdyn.F90
Go to the documentation of this file.
1 MODULE yomdyn
2 
3 USE parkind1 ,ONLY : jpim ,jprb
4 
5 IMPLICIT NONE
6 
7 SAVE
8 
9 ! -------------------------------------------------------------------------
10 
11 !* Control variables for the DYNAMICS
12 
13 !=========== TIME STEPPING ====================================================
14 
15 ! TSTEP : length of the timestep in seconds
16 ! TDT : For leap-frog scheme:
17 ! 2*TSTEP except at the first time step where it is TSTEP
18 ! For a two-time level scheme (semi-Lagrangian), TDT is always TSTEP.
19 ! REPS1 : timefiltering constant applied to t-1
20 ! REPS2 : timefiltering constant applied to t+1
21 ! REPSM1 : timefiltering constant applied to t-1 (moisture vars.)
22 ! REPSM2 : timefiltering constant applied to t+1 (moisture vars.)
23 ! REPSP1 : timefiltering constant applied to t-1 for all surface fields
24 
25 REAL(KIND=JPRB) :: tstep
26 REAL(KIND=JPRB) :: tdt
27 REAL(KIND=JPRB) :: reps1
28 REAL(KIND=JPRB) :: reps2
29 REAL(KIND=JPRB) :: repsm1
30 REAL(KIND=JPRB) :: repsm2
31 REAL(KIND=JPRB) :: repsp1
32 
33 !====== MAIN HORIZONTAL DIFFUSION SCHEME ======================================
34 
35 ! * CHARACTERISTIC TIMES:
36 ! HDIRVOR : for diffusion of vorticity.
37 ! HDIRDIV : for diffusion of divergence.
38 ! HDIRT : for diffusion of temperature.
39 ! HDIRQ : for diffusion of humidity.
40 ! HDIRO3 : for diffusion of ozone.
41 ! HDIRPD : for diffusion of pressure departure (non hydrostatic).
42 ! HDIRVD : for diffusion of vertical divergence (non hydrostatic).
43 ! HDIRSP : for diffusion of surface pressure.
44 
45 ! * REVERSE OF CHARACTERISTIC TIMES:
46 ! HRDIRVOR : for diffusion of vorticity.
47 ! HRDIRDIV : for diffusion of divergence.
48 ! HRDIRT : for diffusion of temperature.
49 ! HRDIRQ : for diffusion of humidity.
50 ! HRDIRO3 : for diffusion of ozone.
51 ! HRDIRPD : for diffusion of pressure departure (non hydrostatic).
52 ! HRDIRVD : for diffusion of vertical divergence (non hydrostatic).
53 ! HRDIRSP : for diffusion of surface pressure.
54 
55 ! RRDXTAU : overall intensity of HD
56 ! RDAMPVOR : local enhancing coefficient for diffusion of vorticity.
57 ! RDAMPDIV : local enhancing coefficient for diffusion of divergence.
58 ! RDAMPT : local enhancing coefficient for diffusion of temperature.
59 ! RDAMPQ : local enhancing coefficient for diffusion of humidity.
60 ! RDAMPO3 : local enhancing coefficient for diffusion of ozone.
61 ! RDAMPPD : local enhancing coefficient for diffusion of pressure departure.
62 ! RDAMPVD : local enhancing coefficient for diffusion of vertical divergence.
63 ! RDAMPSP : local enhancing coefficient for diffusion of surface pressure.
64 ! LREPHD : key to reproduce HD consistency:
65 ! if TRUE the consistency of HDIR[x] is ensured, while namelist
66 ! values of RRDAMP[x] can be slightly modified;
67 ! if FALSE the HD is driven exactly by RRDXTAU and RRDAMP[x]
68 ! but consistency of HDIR[x] is not guarranted
69 ! LNEWHD : only for ECMWF: "new" or "historical" values of HD set-up
70 
71 ! REXPDH : order of the diffusion
72 ! (exponent for the wavenumber dependency).
73 ! FRANDH : threshold for the wavenumber dependency.
74 ! SLEVDH : first threshold for the pressure dependency scaled by VP00.
75 ! SLEVDH2 : second threshold for the pressure dependency scaled by VP00.
76 ! SLEVDH3 : third threshold for the pressure dependency scaled by VP00
77 ! (used to bound the vertical increase of diffusion in the
78 ! upper stratosphere).
79 ! NSREFDH : threshold for the truncation dependency.
80 
81 ! * LEVEL AND WAVENUMBER DEPENDENT INVERSE CHARACTERISTIC TIMES:
82 ! RDIVOR : for diffusion of vorticity.
83 ! RDIDIV : for diffusion of divergence.
84 ! RDITG : for diffusion of temperature.
85 ! RDIGFL : for diffusion of GFL vars.
86 ! RDIPD : for diffusion of pressure departure (NH).
87 ! RDIVD : for diffusion of vertical divergence (NH).
88 ! RDISP : for diffusion of surface pressure.
89 
90 ! GMR : coefficients for spectral multiplication by GM.
91 ! RDHI : main horizontal diffusion operator used for stretched ARPEGE.
92 
93 ! LSTRHD : .T.: main horizontal diffusion operator adapted to stretched ARP.
94 ! HDTIME_STRHD: TDT (if not, the main horizontal diffusion operator
95 ! used for stretched ARPEGE is recomputed).
96 
97 REAL(KIND=JPRB) :: hdirvor
98 REAL(KIND=JPRB) :: hdirdiv
99 REAL(KIND=JPRB) :: hdirt
100 REAL(KIND=JPRB) :: hdirq
101 REAL(KIND=JPRB) :: hdiro3
102 REAL(KIND=JPRB) :: hdirpd
103 REAL(KIND=JPRB) :: hdirvd
104 REAL(KIND=JPRB) :: hdirsp
105 REAL(KIND=JPRB) :: hrdirvor
106 REAL(KIND=JPRB) :: hrdirdiv
107 REAL(KIND=JPRB) :: hrdirt
108 REAL(KIND=JPRB) :: hrdirq
109 REAL(KIND=JPRB) :: hrdiro3
110 REAL(KIND=JPRB) :: hrdirpd
111 REAL(KIND=JPRB) :: hrdirvd
112 REAL(KIND=JPRB) :: hrdirsp
113 REAL(KIND=JPRB) :: rrdxtau
114 REAL(KIND=JPRB) :: rdampvor
115 REAL(KIND=JPRB) :: rdampdiv
116 REAL(KIND=JPRB) :: rdampt
117 REAL(KIND=JPRB) :: rdampq
118 REAL(KIND=JPRB) :: rdampo3
119 REAL(KIND=JPRB) :: rdamppd
120 REAL(KIND=JPRB) :: rdampvd
121 REAL(KIND=JPRB) :: rdampsp
122 LOGICAL :: lrephd
123 LOGICAL :: lnewhd
124 REAL(KIND=JPRB) :: rexpdh
125 REAL(KIND=JPRB) :: frandh
126 REAL(KIND=JPRB) :: slevdh
127 REAL(KIND=JPRB) :: slevdh2
128 REAL(KIND=JPRB) :: slevdh3
129 INTEGER(KIND=JPIM) :: nsrefdh
130 REAL(KIND=JPRB),ALLOCATABLE:: rdivor(:,:)
131 REAL(KIND=JPRB),ALLOCATABLE:: rdidiv(:,:)
132 REAL(KIND=JPRB),ALLOCATABLE:: rditg(:,:)
133 REAL(KIND=JPRB),ALLOCATABLE:: rdigfl(:,:,:)
134 REAL(KIND=JPRB),ALLOCATABLE:: rdipd(:,:)
135 REAL(KIND=JPRB),ALLOCATABLE:: rdivd(:,:)
136 REAL(KIND=JPRB),ALLOCATABLE:: rdisp(:)
137 REAL(KIND=JPRB),ALLOCATABLE:: gmr(:,:)
138 REAL(KIND=JPRB),ALLOCATABLE:: rdhi(:,:,:)
139 LOGICAL :: lstrhd
140 REAL(KIND=JPRB) :: hdtime_strhd
141 
142 !====== SEMI-LAGRANGIAN HORIZONTAL DIFFUSION SCHEME (SLHD) ====================
143 
144 ! * FOR SLHD INTERPOLATIONS:
145 ! SLHDA : Scaling factor of the deformation in f(d) function
146 ! (including the model resolution correction)
147 ! SLHDA0 : Namelist variable allowing to compute SLHDA
148 ! (scaling factor of the deformation in f(d) function
149 ! without the model resolution correction)
150 ! SLHDB : Exponent of the deformation in f(d) function
151 ! SLHDD0 : Treshold for deformation tensor enhancement
152 ! ALPHINT : Limit for the interval of enhancing linear
153 ! S-L interpolation by smoother (should be
154 ! within the interval <0,0.5>)
155 ! GAMMAX : Maximum value for the Gamma function (the weight
156 ! of the smoother for the diffusive S-L interpolator),
157 ! including the timestep correction.
158 ! GAMMAX0 : Namelist variable allowing to compute GAMMAX
159 ! (maximum value for the Gamma function,
160 ! without the timestep correction).
161 ! SLHDKMAX: Maximum value for the Kappa function
162 
163 ! * THE "HDS" CHARACTERISTIC TIMES (obsolete):
164 ! HDSRVOR : for diffusion of vorticity.
165 ! HDSRDIV : for diffusion of divergence.
166 ! HDSRVD : for diffusion of vertical divergence (NH).
167 
168 ! * REVERSE OF THE "HDS" CHARACTERISTIC TIMES:
169 ! HRDSRVOR : for diffusion of vorticity.
170 ! HRDSRDIV : for diffusion of divergence.
171 ! HRDSRVD : for diffusion of vertical divergence (NH).
172 
173 ! RDAMPVORS: local enhancing coefficient for HDS diffusion of vorticity
174 ! RDAMPDIVS: local enhancing coefficient for HDS diffusion of divergence
175 ! RDAMPVDS : local enhancing coefficient for HDS diffusion of vert. divergence
176 ! RDAMPHDS : ratio HRDSRDIV/HRDIRDIV.
177 
178 ! REXPDHS : order of the diffusion
179 ! (exponent for the wavenumber dependency).
180 ! SLEVDHS : first threshold for the pressure dependency scaled by VP00.
181 ! SLEVDHS2 : second threshold for the pressure dependency scaled by VP00.
182 ! SDRED : variable modifying the vertical profile based on SLEVDH
183 ! ( g(l) becomes g(l)-SDRED in the "main" diffusion).
184 
185 ! * "HDS" LEVEL AND WAVENUMBER DEPENDENT INVERSE CHARACTERISTIC TIMES:
186 ! RDSVOR : for diffusion of vorticity.
187 ! RDSDIV : for diffusion of divergence.
188 ! RDSVD : for diffusion of NH vertical divergence variable.
189 ! RDHS : SLHD additional horizontal diffusion operator used for stretched ARPEGE.
190 
191 REAL(KIND=JPRB),ALLOCATABLE :: slhda(:)
192 REAL(KIND=JPRB) :: slhda0
193 REAL(KIND=JPRB) :: slhdb
194 REAL(KIND=JPRB),ALLOCATABLE :: slhdd0(:)
195 REAL(KIND=JPRB) :: alphint
196 REAL(KIND=JPRB) :: gammax
197 REAL(KIND=JPRB) :: gammax0
198 REAL(KIND=JPRB) :: slhdkmax
199 REAL(KIND=JPRB) :: hdsrvor
200 REAL(KIND=JPRB) :: hdsrdiv
201 REAL(KIND=JPRB) :: hdsrvd
202 REAL(KIND=JPRB) :: hrdsrvor
203 REAL(KIND=JPRB) :: hrdsrdiv
204 REAL(KIND=JPRB) :: hrdsrvd
205 REAL(KIND=JPRB) :: rdampvors
206 REAL(KIND=JPRB) :: rdampdivs
207 REAL(KIND=JPRB) :: rdampvds
208 REAL(KIND=JPRB) :: rdamphds
209 REAL(KIND=JPRB) :: rexpdhs
210 REAL(KIND=JPRB) :: slevdhs
211 REAL(KIND=JPRB) :: slevdhs2
212 REAL(KIND=JPRB) :: sdred
213 REAL(KIND=JPRB),ALLOCATABLE:: rdsvor(:,:)
214 REAL(KIND=JPRB),ALLOCATABLE:: rdsdiv(:,:)
215 REAL(KIND=JPRB),ALLOCATABLE:: rdsvd(:,:)
216 REAL(KIND=JPRB),ALLOCATABLE:: rdhs(:,:,:)
217 
218 !================== SPECTRAL ENHANCED DIFFUSION ===============================
219 
220 ! LFREIN : switch to use spectral "enhanced diffusion" (.TRUE. if active)
221 ! LFREINF : same as LFREIN but computed only at STEPO 0 of non-linear run
222 ! LCHDIF : change diffusion coefficients if LFREINF
223 ! FLCCRI : critical value of CFL criterion
224 ! RFREIN : constant for spectral "enhanced diffusion".
225 
226 LOGICAL :: lfrein
227 LOGICAL :: lfreinf
228 LOGICAL :: lchdif
229 REAL(KIND=JPRB) :: flccri
230 REAL(KIND=JPRB) :: rfrein
231 
232 !====== QUANTITIES TO CHANGE THE VARIABLE IN THE T-EQN =======================
233 
234 ! RCORDIT(NFLEVG) : correction term at full-levels for diffusion of T.
235 ! RCORDIH(0:NFLEVG) : correction term at half-levels for SL T-eqn if RCMSMP0/=0
236 ! RCORDIF(NFLEVG) : correction term at full-levels for SL T-eqn if RCMSMP0/=0
237 
238 REAL(KIND=JPRB),ALLOCATABLE:: rcordit(:)
239 REAL(KIND=JPRB),ALLOCATABLE:: rcordih(:)
240 REAL(KIND=JPRB),ALLOCATABLE:: rcordif(:)
241 
242 !==== MAXIMUM V-WINDS ALLOWED IN THE SEMI-LAGRANGIAN MODEL ====================
243 
244 ! VMAX1 : if V>VMAX1 (SM) or SQRT(U**2+V**2)>VMAX1 (DM),
245 ! warning in the SL scheme.
246 ! VMAX2 : if V>VMAX2 (SM) or SQRT(U**2+V**2)>VMAX2 (DM),
247 ! abort in the SL scheme.
248 
249 REAL(KIND=JPRB) :: vmax1
250 REAL(KIND=JPRB) :: vmax2
251 
252 !================== DELTA FORMULATION =========================================
253 
254 ! NDLNPR : NDLNPR=0: conventional formulation of delta, i.e. ln(P(l)/P(l-1)).
255 ! NDLNPR=1: formulation of delta used in non hydrostatic model,
256 ! i.e. (P(l)-P(l-1))/SQRT(P(l)*P(l-1)).
257 
258 INTEGER(KIND=JPIM) :: ndlnpr
259 
260 !==== RAYLEIGH FRICTION =======================================================
261 
262 ! RKRF(NFLEVG) : coefficient of Rayleigh friction
263 
264 REAL(KIND=JPRB),ALLOCATABLE:: rkrf(:)
265 
266 !==== VERTICAL FILTER ========================================================
267 
268 ! LVERFLT : switch to use filter in the vertical
269 ! REPSVFVO: coefficient for 2-del-eta vertical filter on vorticity
270 ! REPSVFDI: coefficient for 2-del-eta vertical filter on divergence
271 ! NLEVVF : vertical filter applied for levs 1 to NLEVVF
272 ! LVERAVE_HLUV: switch to filter (vertically) the half-level wind
273 ! which is computed in routine GPHLUV.
274 
275 LOGICAL :: lverflt
276 REAL(KIND=JPRB) :: repsvfvo
277 REAL(KIND=JPRB) :: repsvfdi
278 INTEGER(KIND=JPIM) :: nlevvf
279 LOGICAL :: lverave_hluv
280 
281 !==== UPPER RADIATIVE BOUNDARY CONDITION ======================================
282 
283 ! RHYDR0 - upper boundary contition for hydrostatic
284 ! RTEMRB - tuning temperature for upper radiative b. c. (LRUBC)
285 ! NRUBC : control of radiative upper boundary condition :
286 ! =0 <=> non computation
287 ! =1 <=> computation on the forecast field
288 ! =2 <=> computation on the departure of the forecast from the coupling field
289 
290 REAL(KIND=JPRB) :: rhydr0
291 REAL(KIND=JPRB) :: rtemrb
292 INTEGER(KIND=JPIM) :: nrubc
293 
294 !==== SEMI-IMPLICIT SCHEME, VERTICAL EIGENMODES, PC SCHEMES ===================
295 
296 ! LSIDG : .F.: Semi-implicit-scheme with reduced divergence.
297 ! .T.: Semi-implicit scheme with not reduced divergence.
298 
299 ! BETADT : coefficient for the semi-implicit treatment of divergence,
300 ! temperature, continuity (and NH if required) equations.
301 ! REFGEO : reference geopotentiel for shallow-water model.
302 ! SIPR : reference surface pressure.
303 ! SITR : reference temperature.
304 ! SITRA : acoustic reference temperature.
305 ! SITRUB : ref. temper. for SI corr. of temper.(for LRUBC=.T.)
306 ! SIPRUB : coef. for SI corr. of surf. press. (for LRUBC=.T.)
307 ! SITIME : =TDT (if not, Helmholtz matrices are recomputed in CNT4).
308 ! SIRPRG : auxiliary variable for SIGAM,SIGAMA.
309 ! SIRPRN : auxiliary variable for SITNU,SITNUA
310 ! NSITER : number of iterations to treat the non linear semi-implicit terms
311 ! in the non-hydrostatic scheme.
312 ! NCURRENT_ITER : for LNHDYN with PC scheme - current iteration:
313 ! 0 - predictor
314 ! 1, 2, ..., NSITER - correctors
315 ! LRHDI_LASTITERPC: T (resp. F): when a PC scheme is activated (for example
316 ! LPC_FULL=.T.), the horizontal diffusion is done at the last iteration
317 ! of the corrector step (resp. all iterations of the predictor-corrector
318 ! scheme).
319 
320 ! * PRESSURES LINKED TO A REFERENCE PRESSURE = SIPR
321 ! SIALPH(NFLEVG) : coefficients "alpha" of hydrostatics.
322 ! SILNPR(NFLEVG) : Log of ratio of pressures between levels.
323 ! SIDELP(NFLEVG) : pressure differences across layers.
324 ! SIRDEL(NFLEVG) : their inverse.
325 ! SITLAH(0:NFLEVG): half-level pressures.
326 ! SITLAF(NFLEVG) : full-level pressures.
327 ! SIDPHI(NFLEVG) : geopotential differences across layers.
328 
329 ! SCGMAP((NSMAX+1)*(NSMAX+2)/2,3): coefficients for multiplication by (GM**2)
330 ! in spectral space.
331 ! SIB(NFLEVG,NFLEVG) : operator "B" of the SI scheme (DIV ===> DP/DT=B.DIV).
332 ! SIMO(NFLEVG,NFLEVG) : eigenvectors of "B".
333 ! SIMI(NFLEVG,NFLEVG) : SIMO**-1
334 ! SIVP(NFLEVG) : eigenvalues of "B".
335 ! SIHEG(NFLEVG,(NSMAX+1)*(NSMAX+2)/2,3), SIHEG2(NFLEVG,NSMAX+1,2:3):
336 ! Helmholtz operator in case of SI computations with not reduced divergence.
337 ! SIHEGB(NFLEVG,(NSMAX+1)*(NSMAX+2)/2,3), SIHEGB2(NFLEVG,NSMAX+1,2:3):
338 ! Additional operators in case of LSIDG=T SI computations in the NH model.
339 ! SITRICA(NSMAX,NFLEVG): ) coefficients used in tridiagonal solver
340 ! SITRICB(NSMAX,NFLEVG): ) for the vertically-coupled semi-implicit
341 ! SITRICC(NSMAX,NFLEVG): ) equations (case LSITRIC=T).
342 
343 ! SIRUB(0:NFLEVG) : Kernel of the operator
344 ! SIGAM SITNU
345 ! (T,ps) -----> P -----> (T,ps)
346 ! 0 is for surface pressure (or its log)
347 ! 1 to NFLEVG is for temperature
348 ! t
349 ! S2ETA(NFLEVG) : S S SIRUB, where S is a Laplacian operator
350 ! used to eliminate the 2 delta eta wave in the vertical temperature field
351 
352 ! SIFAC : [ 1 - beta**2 (Delta t)**2 C**2 (SITR/SITRA) (LLstar/H**2) ]
353 ! for NH model.
354 ! SIFACI: [ 1 - beta**2 (Delta t)**2 C**2 (SITR/SITRA) (LLstar/H**2) ]**(-1)
355 ! for NH model.
356 
357 ! VNORM : constant for new scaling.
358 
359 LOGICAL :: lsidg
360 REAL(KIND=JPRB) :: betadt
361 REAL(KIND=JPRB) :: refgeo
362 REAL(KIND=JPRB) :: sipr
363 REAL(KIND=JPRB) :: sitr
364 REAL(KIND=JPRB) :: sitra
365 REAL(KIND=JPRB) :: sitrub
366 REAL(KIND=JPRB) :: siprub
367 REAL(KIND=JPRB) :: sitime
368 REAL(KIND=JPRB) :: sirprg
369 REAL(KIND=JPRB) :: sirprn
370 INTEGER(KIND=JPIM) :: nsiter
371 INTEGER(KIND=JPIM) :: ncurrent_iter
373 
374 REAL(KIND=JPRB),ALLOCATABLE:: sialph(:)
375 REAL(KIND=JPRB),ALLOCATABLE:: silnpr(:)
376 REAL(KIND=JPRB),ALLOCATABLE:: sidelp(:)
377 REAL(KIND=JPRB),ALLOCATABLE:: sirdel(:)
378 REAL(KIND=JPRB),ALLOCATABLE:: sitlah(:)
379 REAL(KIND=JPRB),ALLOCATABLE:: sitlaf(:)
380 REAL(KIND=JPRB),ALLOCATABLE:: sidphi(:)
381 REAL(KIND=JPRB),ALLOCATABLE:: scgmap(:,:)
382 REAL(KIND=JPRB),ALLOCATABLE:: sib(:,:)
383 REAL(KIND=JPRB),ALLOCATABLE:: simo(:,:)
384 REAL(KIND=JPRB),ALLOCATABLE:: simi(:,:)
385 REAL(KIND=JPRB),ALLOCATABLE:: sivp(:)
386 REAL(KIND=JPRB),ALLOCATABLE:: siheg(:,:,:)
387 REAL(KIND=JPRB),ALLOCATABLE:: siheg2(:,:,:)
388 REAL(KIND=JPRB),ALLOCATABLE:: sihegb(:,:,:)
389 REAL(KIND=JPRB),ALLOCATABLE:: sihegb2(:,:,:)
390 REAL(KIND=JPRB),ALLOCATABLE:: sitrica(:,:)
391 REAL(KIND=JPRB),ALLOCATABLE:: sitricb(:,:)
392 REAL(KIND=JPRB),ALLOCATABLE:: sitricc(:,:)
393 REAL(KIND=JPRB),ALLOCATABLE:: sirub(:)
394 REAL(KIND=JPRB),ALLOCATABLE:: s2eta(:)
395 REAL(KIND=JPRB),ALLOCATABLE:: sifac(:,:)
396 REAL(KIND=JPRB),ALLOCATABLE:: sifaci(:,:)
397 REAL(KIND=JPRB) :: vnorm
398 
399 !=========== SEMI-LAGRANGIAN SWITCHES AND WEIGHTS =============================
400 !=========== + ADDITIONAL "ADVECTION" SWITCHES ALSO USED IN EULERIAN ==========
401 
402 ! * Switches NxLAG:
403 ! NVLAG : switch for formulation or discretisation of continuity equation.
404 ! NWLAG : switch for formulation or discretisation of momentum equations.
405 ! NTLAG : switch for formulation or discretisation of temperature equation.
406 ! NSPDLAG : switch for formulation or discretisation of P-hat equation.
407 ! NSVDLAG : switch for formulation or discretisation of d-hat equation.
408 ! Remarks about NxLAG:
409 ! a) possible value for NxLAG:
410 ! NxLAG=1 -> interpolation of R.H.S. of the corresponding eq.
411 ! to the middle of the trajectory
412 ! NxLAG=2 -> averaging of R.H.S. of the corresponding eq.
413 ! along the trajectory with the part corresponding
414 ! to the departure point added to the t-dt term
415 ! NxLAG=3 -> averaging of R.H.S. of the corresponding eq.
416 ! along the trajectory with the part corresponding
417 ! to the departure point interpolated linearly
418 ! c) For NVLAG and 2D model:
419 ! NVLAG>0 stands for the conventional formulation of continuity equation.
420 ! NVLAG<0 stands for the Lagrangian formulation of continuity equation:
421 ! in this case the remark a) is valid for ABS(NVLAG).
422 
423 ! * Research of semi-Lagrangian trajectory:
424 ! NITMP : Number of iterations for computing the medium point of the
425 ! semi-lagrangian trajectory.
426 ! VETAON : VETAON*eta(layer nr 1)+(1.-VETAON)*eta(top) is the lower
427 ! value allowed for ETA of the origin/anterior point in
428 ! the 3D model.
429 ! VETAOX : VETAOX*eta(bottom layer)+(1.-VETAOX)*eta(ground) is the
430 ! upper value allowed for ETA of the origin/anterior point
431 ! in the 3D model.
432 ! LSETTLS : type of extrapolations needed in the algorithm of trajectory
433 ! research in the 2TL SL scheme.
434 ! .F.: linear extrapolations (conventional algorithm).
435 ! .T.: stable extrapolations combining spatio-temporal extrapolations.
436 ! LELTRA : if TRUE then use "elegant" algorithm to find departure point
437 ! (only applicable in 2TL scheme for the shallow-water equations)
438 ! RW2TLFF : when computing the refined position of the origin point for
439 ! Coriolis term, the new wind used is:
440 ! 0.5*RW2TLFF*(V(F)+V(O)) + (1-RW2TLFF)*V(M)
441 
442 ! * Uncentering factor in the semi-Lagrangian scheme:
443 ! VESL : first order uncentering factor applied to non linear and linear
444 ! terms.
445 ! XIDT : pseudo-second order uncentering factor applied to linear terms,
446 ! when an alternative second-order averaging is required in the
447 ! 2TL SL scheme.
448 ! LPC_XIDT: pseudo second order decentering in LPC_FULL PC scheme
449 ! key used to allocate special buffer for needed quantities
450 ! to transfer informations from predictor to corrector.
451 
452 ! * Switches for use of quasi-monotone interpolations:
453 ! LQMW : Use quasi-monotone three-dimensional interpolations for wind
454 ! LQMHW : Use quasi-monotone interpolations in the horizontal for wind
455 ! LQMT : Use quasi-monotone three-dimensional interpolations for temperature
456 ! LQMHT : Use quasi-monotone interpolations in the horizontal for temperature
457 ! LQMP : Use quasi-monotone three-dimensional interpolations for cont. eq
458 ! LQMHP : Use quasi-monotone interpolations in the horizontal for cont. eq
459 ! LQMPD : Use quasi-monotone three-dimensional interpolations for P-hat eqn.
460 ! LQMHPD : Use quasi-monotone interpolations in the horizontal for P-hat eqn.
461 ! LQMVD : Use quasi-monotone three-dimensional interpolations for d-hat eqn.
462 ! LQMHVD : Use quasi-monotone interpolations in the horizontal for d-hat eqn.
463 
464 ! * Switches for use of spline interpolations:
465 ! LRSPLINE_W : Use of spline for wind
466 ! LRSPLINE_T : Use of spline for temperature
467 ! LRSPLINE_P : Use of spline for continuity equation
468 ! LRSPLINE_SPD : Use of spline for pressure departure
469 ! LRSPLINE_SVD : Use of spline for vertical divergence
470 
471 
472 ! * Treatment of Coriolis term:
473 ! LADVF : if TRUE then use "advective" treatment of Coriolis terms (SL);
474 ! in this case 2*Omega*Vec*r is computed analytically.
475 ! LIMPF : if TRUE then use implicit treatment of Coriolis terms (EUL and SL)
476 ! L2TLFF : if TRUE then use refined treatment of Coriolis term in 2TLSL scheme
477 ! (can be currently used also with the 3TL SL vertical interpolating
478 ! scheme).
479 
480 ! * Change variable with an Eulerian treatment of orography:
481 ! RCMSLP0 : Real for tuning of the Tanguay/Ritchie correction in SL continuity
482 ! and temperature equations for 3D model.
483 
484 ! * Treatment of MF simplified physics in the semi-Lagrangian TL and AD codes.
485 
486 ! LSL_UNLPHY_F : if TRUE diabatic terms are evaluated at the final point F.
487 ! if FALSE diabatic terms are evaluated at the orig point O.
488 ! Remark: this variable is involved only in MF physics.
489 
490 ! * Switch for computation of Moisture Convergence for French deep convection scheme
491 
492 ! NCOMP_CVGQ : 0 ==> Compute the CVGQ in an Eulerian manner, using spectral
493 ! moisture stored in the YQ GFL variable.
494 ! In this case YQ must be spectral and
495 ! horizontal derivatives are used.
496 ! 1 ==> Compute the CVGQ in an Eulerian manner, using spectral
497 ! moisture stored in the YCVGQ GFL spectral variable and
498 ! its horizontal derivatives.
499 ! This case is well designed for the case where YQ is
500 ! a purely grid-point GFL.
501 ! 2 ==> Compute the CVGQ in a semi-Lagrangian manner
502 ! (Lagrangian tendency - Eulerian tendency), using data
503 ! stored in the YCVGQ grid-point variable.
504 ! This case is well designed for the case where YQ is
505 ! a purely grid-point GFL, and where LSLAG=T.
506 ! remark ky: better to move this variable in SUDYNA/NAMDYNA/YOMDYNA in the
507 ! future to make it available in SUDIM1 when reading NAMGFL.
508 
509 INTEGER(KIND=JPIM) :: nvlag
510 INTEGER(KIND=JPIM) :: nwlag
511 INTEGER(KIND=JPIM) :: ntlag
512 INTEGER(KIND=JPIM) :: nspdlag
513 INTEGER(KIND=JPIM) :: nsvdlag
514 INTEGER(KIND=JPIM) :: nitmp
515 REAL(KIND=JPRB) :: vetaon
516 REAL(KIND=JPRB) :: vetaox
517 LOGICAL :: lsettls
518 LOGICAL :: leltra
519 REAL(KIND=JPRB) :: rw2tlff
520 REAL(KIND=JPRB) :: vesl
521 REAL(KIND=JPRB) :: xidt
522 LOGICAL :: lpc_xidt
523 LOGICAL :: lqmw
524 LOGICAL :: lqmhw
525 LOGICAL :: lqmt
526 LOGICAL :: lqmht
527 LOGICAL :: lqmp
528 LOGICAL :: lqmhp
529 LOGICAL :: lqmpd
530 LOGICAL :: lqmhpd
531 LOGICAL :: lqmvd
532 LOGICAL :: lqmhvd
533 LOGICAL :: ladvf
534 LOGICAL :: lrspline_w
535 LOGICAL :: lrspline_t
536 LOGICAL :: lrspline_p
537 LOGICAL :: lrspline_spd
538 LOGICAL :: lrspline_svd
539 LOGICAL :: limpf
540 LOGICAL :: l2tlff
541 REAL(KIND=JPRB) :: rcmslp0
542 LOGICAL :: lsl_unlphy_f
543 INTEGER(KIND=JPIM) :: ncomp_cvgq
544 
545 !=========== RELAXATION OF THIN LAYER HYPOTHESIS ==============================
546 ! (for more details about "rs", "Ts" see routines gpvcrs.F90 and gpvcts.F90)
547 
548 ! VCPR : reference pressure (the pressure layer where "rs=a")
549 ! VCTR : reference temperature (VCTR=Ts(pressure=VCPR))
550 ! VCAK : coefficient alpha_K used in tha analytic formula of "Ts".
551 ! LADVFW : as LADVF but for term "-2 Omega vec W k".
552 
553 REAL(KIND=JPRB) :: vcpr
554 REAL(KIND=JPRB) :: vctr
555 REAL(KIND=JPRB) :: vcak
556 LOGICAL :: ladvfw
557 
558 ! ------------------------------------------------------------------
559 ! LDRY_ECMWF : .TRUE. = COMPUTE Cp, R AND R/Cp WITHOUT Q REALTED TERMS
560 ! LDRY_ECMWF : .FALSE. = COMPUTE Cp, R AND R/Cp WITH Q REALTED TERMS
561 
562 LOGICAL :: ldry_ecmwf
563 
564 ! ------------------------------------------------------------------
565 !$OMP THREADPRIVATE(alphint,betadt,flccri,frandh,gammax,gammax0,hdirdiv,hdiro3,hdirpd,hdirq,hdirsp,hdirt)
566 !$OMP THREADPRIVATE(hdirvd,hdirvor,hdsrdiv,hdsrvd,hdsrvor,hdtime_strhd,hrdirdiv,hrdiro3,hrdirpd,hrdirq)
567 !$OMP THREADPRIVATE(hrdirsp,hrdirt,hrdirvd,hrdirvor,hrdsrdiv,hrdsrvd,hrdsrvor,l2tlff,ladvf,ladvfw,lchdif)
568 !$OMP THREADPRIVATE(ldry_ecmwf,leltra,lfrein,lfreinf,limpf,lnewhd,lpc_xidt,lqmhp,lqmhpd,lqmht,lqmhvd,lqmhw)
569 !$OMP THREADPRIVATE(lqmp,lqmpd,lqmt,lqmvd,lqmw,lrephd,lrhdi_lastiterpc,lrspline_p,lrspline_spd,lrspline_svd)
570 !$OMP THREADPRIVATE(lrspline_t,lrspline_w,lsettls,lsidg,lsl_unlphy_f,lstrhd,lverave_hluv,lverflt,ncomp_cvgq)
571 !$OMP THREADPRIVATE(ncurrent_iter,ndlnpr,nitmp,nlevvf,nrubc,nsiter,nspdlag,nsrefdh,nsvdlag,ntlag,nvlag,nwlag)
572 !$OMP THREADPRIVATE(rcmslp0,rdampdiv,rdampdivs,rdamphds,rdampo3,rdamppd,rdampq,rdampsp,rdampt,rdampvd,rdampvds)
573 !$OMP THREADPRIVATE(rdampvor,rdampvors,refgeo,reps1,reps2,repsm1,repsm2,repsp1,repsvfdi,repsvfvo,rexpdh,rexpdhs)
574 !$OMP THREADPRIVATE(rfrein,rhydr0,rrdxtau,rtemrb,rw2tlff,sdred,sipr,siprub,sirprg,sirprn,sitime,sitr,sitra,sitrub)
575 !$OMP THREADPRIVATE(slevdh,slevdh2,slevdh3,slevdhs,slevdhs2,slhda0,slhdb,slhdkmax,tdt,tstep,vcak,vcpr,vctr,vesl)
576 !$OMP THREADPRIVATE(vetaon,vetaox,vmax1,vmax2,vnorm,xidt)
577 !$OMP THREADPRIVATE(gmr,rcordif,rcordih,rcordit,rdhi,rdhs,rdidiv,rdigfl,rdipd,rdisp,rditg,rdivd,rdivor,rdsdiv)
578 !$OMP THREADPRIVATE(rdsvd,rdsvor,rkrf,s2eta,scgmap,sialph,sib,sidelp,sidphi,sifac,sifaci,siheg,siheg2,sihegb)
579 !$OMP THREADPRIVATE(sihegb2,silnpr,simi,simo,sirdel,sirub,sitlaf,sitlah,sitrica,sitricb,sitricc,sivp,slhda,slhdd0)
580 END MODULE yomdyn
real(kind=jprb) gammax0
Definition: yomdyn.F90:197
real(kind=jprb), dimension(:,:), allocatable rdivor
Definition: yomdyn.F90:130
real(kind=jprb) sitr
Definition: yomdyn.F90:363
real(kind=jprb), dimension(:,:), allocatable simo
Definition: yomdyn.F90:383
logical lsettls
Definition: yomdyn.F90:517
real(kind=jprb) slevdhs2
Definition: yomdyn.F90:211
real(kind=jprb) vctr
Definition: yomdyn.F90:554
real(kind=jprb), dimension(:,:), allocatable sitricb
Definition: yomdyn.F90:391
real(kind=jprb), dimension(:,:), allocatable sitrica
Definition: yomdyn.F90:390
real(kind=jprb) rdamphds
Definition: yomdyn.F90:208
logical lrephd
Definition: yomdyn.F90:122
logical ladvf
Definition: yomdyn.F90:533
real(kind=jprb) slevdh3
Definition: yomdyn.F90:128
real(kind=jprb) rdampvor
Definition: yomdyn.F90:114
real(kind=jprb) hrdirvor
Definition: yomdyn.F90:105
real(kind=jprb), dimension(:), allocatable s2eta
Definition: yomdyn.F90:394
real(kind=jprb), dimension(:), allocatable slhda
Definition: yomdyn.F90:191
real(kind=jprb) rfrein
Definition: yomdyn.F90:230
real(kind=jprb) slhdb
Definition: yomdyn.F90:193
real(kind=jprb) rdampvors
Definition: yomdyn.F90:205
real(kind=jprb), dimension(:,:,:), allocatable sihegb2
Definition: yomdyn.F90:389
real(kind=jprb) xidt
Definition: yomdyn.F90:521
real(kind=jprb) rdamppd
Definition: yomdyn.F90:119
logical lrspline_w
Definition: yomdyn.F90:534
real(kind=jprb) rw2tlff
Definition: yomdyn.F90:519
real(kind=jprb), dimension(:,:,:), allocatable rdhi
Definition: yomdyn.F90:138
logical ldry_ecmwf
Definition: yomdyn.F90:562
real(kind=jprb) refgeo
Definition: yomdyn.F90:361
real(kind=jprb) hdtime_strhd
Definition: yomdyn.F90:140
real(kind=jprb) sipr
Definition: yomdyn.F90:362
real(kind=jprb) tdt
Definition: yomdyn.F90:26
logical lqmhw
Definition: yomdyn.F90:524
real(kind=jprb) reps2
Definition: yomdyn.F90:28
real(kind=jprb), dimension(:,:,:), allocatable rdigfl
Definition: yomdyn.F90:133
real(kind=jprb), dimension(:,:), allocatable gmr
Definition: yomdyn.F90:137
real(kind=jprb) hrdsrvor
Definition: yomdyn.F90:202
logical lnewhd
Definition: yomdyn.F90:123
real(kind=jprb) rdampdivs
Definition: yomdyn.F90:206
real(kind=jprb), dimension(:), allocatable slhdd0
Definition: yomdyn.F90:194
real(kind=jprb) hrdiro3
Definition: yomdyn.F90:109
real(kind=jprb) hrdirdiv
Definition: yomdyn.F90:106
real(kind=jprb) slevdhs
Definition: yomdyn.F90:210
real(kind=jprb) hdsrvor
Definition: yomdyn.F90:199
logical lsidg
Definition: yomdyn.F90:359
real(kind=jprb), dimension(:,:), allocatable rdipd
Definition: yomdyn.F90:134
integer(kind=jpim) nvlag
Definition: yomdyn.F90:509
logical lsl_unlphy_f
Definition: yomdyn.F90:542
real(kind=jprb), dimension(:,:), allocatable sitricc
Definition: yomdyn.F90:392
logical lrspline_svd
Definition: yomdyn.F90:538
real(kind=jprb) hrdirq
Definition: yomdyn.F90:108
logical lstrhd
Definition: yomdyn.F90:139
real(kind=jprb), dimension(:), allocatable rcordit
Definition: yomdyn.F90:238
real(kind=jprb) sitra
Definition: yomdyn.F90:364
real(kind=jprb), dimension(:), allocatable silnpr
Definition: yomdyn.F90:375
logical lverflt
Definition: yomdyn.F90:275
real(kind=jprb) repsvfdi
Definition: yomdyn.F90:277
logical lqmhvd
Definition: yomdyn.F90:532
real(kind=jprb) rhydr0
Definition: yomdyn.F90:290
integer(kind=jpim) ncomp_cvgq
Definition: yomdyn.F90:543
real(kind=jprb) rexpdhs
Definition: yomdyn.F90:209
logical lverave_hluv
Definition: yomdyn.F90:279
real(kind=jprb) slevdh2
Definition: yomdyn.F90:127
real(kind=jprb) hdsrvd
Definition: yomdyn.F90:201
real(kind=jprb) slhda0
Definition: yomdyn.F90:192
logical lqmhp
Definition: yomdyn.F90:528
real(kind=jprb) vmax1
Definition: yomdyn.F90:249
integer(kind=jpim) nitmp
Definition: yomdyn.F90:514
real(kind=jprb) hdirt
Definition: yomdyn.F90:99
real(kind=jprb) rdampq
Definition: yomdyn.F90:117
integer(kind=jpim) ncurrent_iter
Definition: yomdyn.F90:371
logical lqmvd
Definition: yomdyn.F90:531
real(kind=jprb) flccri
Definition: yomdyn.F90:229
logical lpc_xidt
Definition: yomdyn.F90:522
real(kind=jprb) betadt
Definition: yomdyn.F90:360
real(kind=jprb) vetaon
Definition: yomdyn.F90:515
integer(kind=jpim) nrubc
Definition: yomdyn.F90:292
real(kind=jprb) sitrub
Definition: yomdyn.F90:365
real(kind=jprb), dimension(:,:,:), allocatable siheg2
Definition: yomdyn.F90:387
integer(kind=jpim) nsrefdh
Definition: yomdyn.F90:129
real(kind=jprb) vcak
Definition: yomdyn.F90:555
integer(kind=jpim) nspdlag
Definition: yomdyn.F90:512
real(kind=jprb) rcmslp0
Definition: yomdyn.F90:541
real(kind=jprb) vcpr
Definition: yomdyn.F90:553
real(kind=jprb) hdiro3
Definition: yomdyn.F90:101
real(kind=jprb), dimension(:,:), allocatable sifaci
Definition: yomdyn.F90:396
real(kind=jprb) sirprn
Definition: yomdyn.F90:369
real(kind=jprb), dimension(:,:), allocatable rdivd
Definition: yomdyn.F90:135
real(kind=jprb), dimension(:), allocatable rkrf
Definition: yomdyn.F90:264
integer, parameter jprb
Definition: parkind1.F90:31
real(kind=jprb), dimension(:), allocatable sialph
Definition: yomdyn.F90:374
real(kind=jprb), dimension(:,:), allocatable sifac
Definition: yomdyn.F90:395
real(kind=jprb) repsvfvo
Definition: yomdyn.F90:276
logical lqmht
Definition: yomdyn.F90:526
real(kind=jprb) rdampt
Definition: yomdyn.F90:116
real(kind=jprb) hdirpd
Definition: yomdyn.F90:102
logical lrspline_p
Definition: yomdyn.F90:536
real(kind=jprb), dimension(:,:), allocatable simi
Definition: yomdyn.F90:384
real(kind=jprb), dimension(:,:), allocatable rdsdiv
Definition: yomdyn.F90:214
real(kind=jprb) hdsrdiv
Definition: yomdyn.F90:200
real(kind=jprb) gammax
Definition: yomdyn.F90:196
logical l2tlff
Definition: yomdyn.F90:540
real(kind=jprb) vnorm
Definition: yomdyn.F90:397
real(kind=jprb) hdirvor
Definition: yomdyn.F90:97
logical ladvfw
Definition: yomdyn.F90:556
real(kind=jprb) hdirsp
Definition: yomdyn.F90:104
real(kind=jprb) hdirq
Definition: yomdyn.F90:100
integer(kind=jpim) nlevvf
Definition: yomdyn.F90:278
real(kind=jprb), dimension(:,:), allocatable sib
Definition: yomdyn.F90:382
real(kind=jprb) hrdsrdiv
Definition: yomdyn.F90:203
real(kind=jprb) slevdh
Definition: yomdyn.F90:126
logical lqmhpd
Definition: yomdyn.F90:530
logical lrspline_spd
Definition: yomdyn.F90:537
logical limpf
Definition: yomdyn.F90:539
real(kind=jprb) hrdirvd
Definition: yomdyn.F90:111
real(kind=jprb) rdampdiv
Definition: yomdyn.F90:115
real(kind=jprb) alphint
Definition: yomdyn.F90:195
real(kind=jprb) hdirdiv
Definition: yomdyn.F90:98
logical lfreinf
Definition: yomdyn.F90:227
real(kind=jprb), dimension(:,:,:), allocatable rdhs
Definition: yomdyn.F90:216
real(kind=jprb), dimension(:), allocatable sirub
Definition: yomdyn.F90:393
real(kind=jprb), dimension(:,:), allocatable rdsvor
Definition: yomdyn.F90:213
real(kind=jprb), dimension(:), allocatable sirdel
Definition: yomdyn.F90:377
logical lfrein
Definition: yomdyn.F90:226
real(kind=jprb) rtemrb
Definition: yomdyn.F90:291
real(kind=jprb) tstep
Definition: yomdyn.F90:25
real(kind=jprb), dimension(:), allocatable sidphi
Definition: yomdyn.F90:380
real(kind=jprb) hrdirpd
Definition: yomdyn.F90:110
real(kind=jprb), dimension(:), allocatable sitlah
Definition: yomdyn.F90:378
real(kind=jprb), dimension(:), allocatable sidelp
Definition: yomdyn.F90:376
real(kind=jprb) rdampo3
Definition: yomdyn.F90:118
logical lqmpd
Definition: yomdyn.F90:529
real(kind=jprb), dimension(:), allocatable rcordih
Definition: yomdyn.F90:239
real(kind=jprb) sirprg
Definition: yomdyn.F90:368
real(kind=jprb), dimension(:,:,:), allocatable sihegb
Definition: yomdyn.F90:388
real(kind=jprb) siprub
Definition: yomdyn.F90:366
real(kind=jprb), dimension(:,:), allocatable scgmap
Definition: yomdyn.F90:381
real(kind=jprb) rdampvds
Definition: yomdyn.F90:207
real(kind=jprb) rexpdh
Definition: yomdyn.F90:124
real(kind=jprb) rdampvd
Definition: yomdyn.F90:120
real(kind=jprb), dimension(:), allocatable sivp
Definition: yomdyn.F90:385
real(kind=jprb) rrdxtau
Definition: yomdyn.F90:113
real(kind=jprb) hdirvd
Definition: yomdyn.F90:103
Definition: yomdyn.F90:1
real(kind=jprb) vetaox
Definition: yomdyn.F90:516
logical lrspline_t
Definition: yomdyn.F90:535
real(kind=jprb), dimension(:,:), allocatable rdidiv
Definition: yomdyn.F90:131
real(kind=jprb), dimension(:,:), allocatable rdsvd
Definition: yomdyn.F90:215
real(kind=jprb) rdampsp
Definition: yomdyn.F90:121
logical lrhdi_lastiterpc
Definition: yomdyn.F90:372
real(kind=jprb) repsm2
Definition: yomdyn.F90:30
real(kind=jprb) sdred
Definition: yomdyn.F90:212
real(kind=jprb) hrdsrvd
Definition: yomdyn.F90:204
real(kind=jprb), dimension(:,:), allocatable rditg
Definition: yomdyn.F90:132
integer, parameter jpim
Definition: parkind1.F90:13
real(kind=jprb) hrdirt
Definition: yomdyn.F90:107
integer(kind=jpim) ntlag
Definition: yomdyn.F90:511
real(kind=jprb) slhdkmax
Definition: yomdyn.F90:198
real(kind=jprb) hrdirsp
Definition: yomdyn.F90:112
real(kind=jprb), dimension(:), allocatable sitlaf
Definition: yomdyn.F90:379
logical lqmt
Definition: yomdyn.F90:525
integer(kind=jpim) nsvdlag
Definition: yomdyn.F90:513
integer(kind=jpim) ndlnpr
Definition: yomdyn.F90:258
real(kind=jprb), dimension(:,:,:), allocatable siheg
Definition: yomdyn.F90:386
logical leltra
Definition: yomdyn.F90:518
real(kind=jprb) repsm1
Definition: yomdyn.F90:29
real(kind=jprb), dimension(:), allocatable rcordif
Definition: yomdyn.F90:240
real(kind=jprb) vmax2
Definition: yomdyn.F90:250
real(kind=jprb) frandh
Definition: yomdyn.F90:125
real(kind=jprb) reps1
Definition: yomdyn.F90:27
real(kind=jprb) vesl
Definition: yomdyn.F90:520
logical lqmp
Definition: yomdyn.F90:527
logical lqmw
Definition: yomdyn.F90:523
integer(kind=jpim) nwlag
Definition: yomdyn.F90:510
logical lchdif
Definition: yomdyn.F90:228
real(kind=jprb), dimension(:), allocatable rdisp
Definition: yomdyn.F90:136
integer(kind=jpim) nsiter
Definition: yomdyn.F90:370
real(kind=jprb) sitime
Definition: yomdyn.F90:367
real(kind=jprb) repsp1
Definition: yomdyn.F90:31