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 |
---|
372 | LOGICAL :: LRHDI_LASTITERPC |
---|
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 |
---|