1 | ! |
---|
2 | ! |
---|
3 | ! |
---|
4 | SUBROUTINE thermcell_flux(ngrid,nlay,ptimestep,masse, & |
---|
5 | lalim,lmin,lmax,alim_star,entr_star,detr_star, & |
---|
6 | f,rhobarz,zlev,zw2,fm,entr, & |
---|
7 | detr,zqla,lev_out,lunout1,igout) |
---|
8 | |
---|
9 | |
---|
10 | !============================================================================== |
---|
11 | ! thermcell_flux: deduction des flux |
---|
12 | !============================================================================== |
---|
13 | |
---|
14 | USE print_control_mod, ONLY: prt_level |
---|
15 | USE thermcell_mod |
---|
16 | |
---|
17 | IMPLICIT NONE |
---|
18 | |
---|
19 | |
---|
20 | !============================================================================== |
---|
21 | ! Declaration |
---|
22 | !============================================================================== |
---|
23 | |
---|
24 | ! inputs: |
---|
25 | ! ------- |
---|
26 | |
---|
27 | INTEGER ngrid |
---|
28 | INTEGER nlay |
---|
29 | INTEGER igout |
---|
30 | INTEGER lev_out |
---|
31 | INTEGER lunout1 |
---|
32 | INTEGER lmin(ngrid) |
---|
33 | INTEGER lmax(ngrid) |
---|
34 | INTEGER lalim(ngrid) |
---|
35 | |
---|
36 | REAL alim_star(ngrid,nlay) |
---|
37 | REAL entr_star(ngrid,nlay) |
---|
38 | REAL detr_star(ngrid,nlay) |
---|
39 | REAL zw2(ngrid,nlay+1) |
---|
40 | REAL zlev(ngrid,nlay+1) |
---|
41 | REAL masse(ngrid,nlay) |
---|
42 | REAL ptimestep |
---|
43 | REAL rhobarz(ngrid,nlay) |
---|
44 | REAL f(ngrid) |
---|
45 | REAL zqla(ngrid,nlay) |
---|
46 | REAL zmax(ngrid) |
---|
47 | |
---|
48 | ! outputs: |
---|
49 | ! -------- |
---|
50 | |
---|
51 | REAL entr(ngrid,nlay) |
---|
52 | REAL detr(ngrid,nlay) |
---|
53 | REAL fm(ngrid,nlay+1) |
---|
54 | |
---|
55 | ! local: |
---|
56 | ! ------ |
---|
57 | |
---|
58 | INTEGER ig,l,k |
---|
59 | INTEGER lout |
---|
60 | |
---|
61 | REAL zfm ! mass flux such as updraft fraction is equal to its maximal authorized value alphamax |
---|
62 | REAL f_old ! save initial value of mass flux |
---|
63 | REAL eee0 ! save initial value of entrainment |
---|
64 | REAL ddd0 ! save initial value of detrainment |
---|
65 | REAL eee ! eee0 - layer mass * maximal authorized mass fraction / dt |
---|
66 | REAL ddd ! ddd0 - eee |
---|
67 | REAL zzz ! temporary variable set to mass flux |
---|
68 | REAL fact |
---|
69 | REAL test |
---|
70 | |
---|
71 | INTEGER ncorecfm1 |
---|
72 | INTEGER ncorecfm2 |
---|
73 | INTEGER ncorecfm3 |
---|
74 | INTEGER ncorecfm4 |
---|
75 | INTEGER ncorecfm5 |
---|
76 | INTEGER ncorecfm6 |
---|
77 | INTEGER ncorecalpha |
---|
78 | |
---|
79 | LOGICAL check_debug |
---|
80 | LOGICAL labort_physic |
---|
81 | |
---|
82 | CHARACTER (len=20) :: modname='thermcell_flux' |
---|
83 | CHARACTER (len=80) :: abort_message |
---|
84 | |
---|
85 | !============================================================================== |
---|
86 | ! Initialization |
---|
87 | !============================================================================== |
---|
88 | |
---|
89 | ncorecfm1 = 0 |
---|
90 | ncorecfm2 = 0 |
---|
91 | ncorecfm3 = 0 |
---|
92 | ncorecfm4 = 0 |
---|
93 | ncorecfm5 = 0 |
---|
94 | ncorecfm6 = 0 |
---|
95 | |
---|
96 | ncorecalpha = 0 |
---|
97 | |
---|
98 | entr(:,:) = 0. |
---|
99 | detr(:,:) = 0. |
---|
100 | fm(:,:) = 0. |
---|
101 | |
---|
102 | IF (prt_level.ge.10) THEN |
---|
103 | write(lunout1,*) 'Dans thermcell_flux 0' |
---|
104 | write(lunout1,*) 'flux base ', f(igout) |
---|
105 | write(lunout1,*) 'lmax ', lmax(igout) |
---|
106 | write(lunout1,*) 'lalim ', lalim(igout) |
---|
107 | write(lunout1,*) 'ig= ', igout |
---|
108 | write(lunout1,*) ' l E* A* D* ' |
---|
109 | write(lunout1,'(i4,3e15.5)') (l,entr_star(igout,l), & |
---|
110 | & alim_star(igout,l),detr_star(igout,l), & |
---|
111 | & l=1,lmax(igout)) |
---|
112 | ENDIF |
---|
113 | |
---|
114 | !============================================================================== |
---|
115 | ! Calcul de l'entrainement, du detrainement et du flux de masse |
---|
116 | !============================================================================== |
---|
117 | |
---|
118 | !------------------------------------------------------------------------------ |
---|
119 | ! Multiplication par la norme issue de la relation de fermeture |
---|
120 | !------------------------------------------------------------------------------ |
---|
121 | |
---|
122 | DO l=1,nlay |
---|
123 | entr(:,l) = f(:) * (entr_star(:,l) + alim_star(:,l)) |
---|
124 | detr(:,l) = f(:) * detr_star(:,l) |
---|
125 | ENDDO |
---|
126 | |
---|
127 | !------------------------------------------------------------------------------ |
---|
128 | ! Calcul du flux de masse |
---|
129 | !------------------------------------------------------------------------------ |
---|
130 | |
---|
131 | DO l=1,nlay |
---|
132 | DO ig=1,ngrid |
---|
133 | IF (l.lt.lmax(ig) .and. l.ge.lmin(ig)) THEN |
---|
134 | fm(ig,l+1) = fm(ig,l) + entr(ig,l) - detr(ig,l) |
---|
135 | ELSEIF (l.eq.lmax(ig)) THEN |
---|
136 | fm(ig,l+1) = 0. |
---|
137 | detr(ig,l) = fm(ig,l) + entr(ig,l) |
---|
138 | ELSE |
---|
139 | fm(ig,l+1) = 0. |
---|
140 | entr(ig,l) = 0. |
---|
141 | detr(ig,l) = 0. |
---|
142 | ENDIF |
---|
143 | ENDDO |
---|
144 | ENDDO |
---|
145 | |
---|
146 | !============================================================================== |
---|
147 | ! Tests de validite |
---|
148 | !============================================================================== |
---|
149 | |
---|
150 | DO l=1,nlay |
---|
151 | |
---|
152 | !------------------------------------------------------------------------------ |
---|
153 | ! Verification de la positivite du flux de masse entrant |
---|
154 | !------------------------------------------------------------------------------ |
---|
155 | |
---|
156 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
157 | ! AB : I remove the correction and replace it by an uncompromising test. |
---|
158 | ! According to the previous derivations, we MUST have positive mass flux |
---|
159 | ! everywhere! Indeed, as soon as fm becomes negative, the plume stops. |
---|
160 | ! Then the only value which can be negative is the mass flux at the top of |
---|
161 | ! the plume. However, this value was set to zero a few lines above. |
---|
162 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
163 | |
---|
164 | labort_physic=.false. |
---|
165 | |
---|
166 | DO ig=1,ngrid |
---|
167 | IF (fm(ig,l).lt.0.) THEN |
---|
168 | labort_physic = .true. |
---|
169 | igout = ig |
---|
170 | lout = l |
---|
171 | ENDIF |
---|
172 | ENDDO |
---|
173 | |
---|
174 | IF (labort_physic) THEN |
---|
175 | print *, 'ERROR: mass flux has negative value(s)!' |
---|
176 | print *, 'ig,l,fm',igout, lout, fm(igout,lout) |
---|
177 | print *, 'lmin,lmax', lmin(igout), lmax(igout) |
---|
178 | print *, '-------------------------------' |
---|
179 | print *, 'fm+', fm(igout,lout+1) |
---|
180 | print *, 'entr,detr', entr(igout,lout), detr(igout,lout) |
---|
181 | print *, 'fm ', fm(igout,lout) |
---|
182 | print *, 'entr,detr', entr(igout,lout-1), detr(igout,lout-1) |
---|
183 | print *, 'fm-', fm(igout,lout-1) |
---|
184 | abort_message = 'Negative incoming fm in thermcell_flux' |
---|
185 | CALL abort_physic(modname,abort_message,1) |
---|
186 | ENDIF |
---|
187 | |
---|
188 | !------------------------------------------------------------------------------ |
---|
189 | ! Test entrainment positif |
---|
190 | !------------------------------------------------------------------------------ |
---|
191 | |
---|
192 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
193 | ! AB : According to the previous derivations, we MUST have positive entrainment |
---|
194 | ! and detrainment everywhere! |
---|
195 | ! Indeed, they are set to max between zero and a computed value. |
---|
196 | ! Then tests are uncompromising. |
---|
197 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
198 | |
---|
199 | labort_physic=.false. |
---|
200 | |
---|
201 | DO ig=1,ngrid |
---|
202 | IF (entr(ig,l).lt.0.) THEN |
---|
203 | labort_physic = .true. |
---|
204 | igout = ig |
---|
205 | lout = l |
---|
206 | ENDIF |
---|
207 | ENDDO |
---|
208 | |
---|
209 | IF (labort_physic) THEN |
---|
210 | print *, 'ERROR: entrainment has negative value(s)!' |
---|
211 | print *, 'ig,l,entr', igout, lout, entr(igout,lout) |
---|
212 | print *, 'lmin,lmax', lmin(igout), lmax(igout) |
---|
213 | print *, '-------------------------------' |
---|
214 | print *, 'fm+', fm(igout,lout+1) |
---|
215 | print *, 'entr,detr', entr(igout,lout), detr(igout,lout) |
---|
216 | print *, 'fm ', fm(igout,lout) |
---|
217 | print *, 'entr,detr', entr(igout,lout-1), detr(igout,lout-1) |
---|
218 | print *, 'fm-', fm(igout,lout-1) |
---|
219 | abort_message = 'Negative entrainment in thermcell_flux' |
---|
220 | CALL abort_physic(modname,abort_message,1) |
---|
221 | ENDIF |
---|
222 | |
---|
223 | !------------------------------------------------------------------------------ |
---|
224 | ! Test detrainment positif |
---|
225 | !------------------------------------------------------------------------------ |
---|
226 | |
---|
227 | DO ig=1,ngrid |
---|
228 | IF (detr(ig,l).lt.0.) THEN |
---|
229 | labort_physic = .true. |
---|
230 | igout = ig |
---|
231 | lout = l |
---|
232 | ENDIF |
---|
233 | ENDDO |
---|
234 | |
---|
235 | IF (labort_physic) THEN |
---|
236 | print *, 'ERROR: detrainment has negative value(s)!' |
---|
237 | print *, 'ig,l,detr', igout, lout, detr(igout,lout) |
---|
238 | print *, 'lmin,lmax', lmin(igout), lmax(igout) |
---|
239 | print *, '-------------------------------' |
---|
240 | print *, 'fm+', fm(igout,lout+1) |
---|
241 | print *, 'entr,detr', entr(igout,lout), detr(igout,lout) |
---|
242 | print *, 'fm ', fm(igout,lout) |
---|
243 | print *, 'entr,detr', entr(igout,lout-1), detr(igout,lout-1) |
---|
244 | print *, 'fm-', fm(igout,lout-1) |
---|
245 | abort_message = 'Negative detrainment in thermcell_flux' |
---|
246 | CALL abort_physic(modname,abort_message,1) |
---|
247 | ENDIF |
---|
248 | |
---|
249 | !------------------------------------------------------------------------------ |
---|
250 | ! Test sur fraca constante ou croissante au-dessus de lalim |
---|
251 | !------------------------------------------------------------------------------ |
---|
252 | |
---|
253 | ! AB : Do we have to decree that? If so, set iflag_thermals_optflux to 0 |
---|
254 | IF (iflag_thermals_optflux==0) THEN |
---|
255 | DO ig=1,ngrid |
---|
256 | IF (l.ge.lalim(ig).and.l.le.lmax(ig).and.(zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10) ) THEN |
---|
257 | zzz = fm(ig,l) * rhobarz(ig,l+1) * zw2(ig,l+1) & |
---|
258 | & / (rhobarz(ig,l) * zw2(ig,l)) |
---|
259 | |
---|
260 | IF (fm(ig,l+1).gt.zzz) THEN |
---|
261 | detr(ig,l) = detr(ig,l) + fm(ig,l+1) - zzz |
---|
262 | fm(ig,l+1) = zzz |
---|
263 | ncorecfm4 = ncorecfm4 + 1 |
---|
264 | ENDIF |
---|
265 | ENDIF |
---|
266 | ENDDO |
---|
267 | ENDIF |
---|
268 | |
---|
269 | !------------------------------------------------------------------------------ |
---|
270 | ! Test sur flux de masse constant ou decroissant au-dessus de lalim |
---|
271 | !------------------------------------------------------------------------------ |
---|
272 | |
---|
273 | ! AB : Do we have to decree that? If so, set iflag_thermals_optflux to 0 |
---|
274 | IF (iflag_thermals_optflux==0) THEN |
---|
275 | DO ig=1,ngrid |
---|
276 | IF ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then |
---|
277 | f_old = fm(ig,l+1) |
---|
278 | fm(ig,l+1) = fm(ig,l) |
---|
279 | detr(ig,l) = detr(ig,l) + f_old - fm(ig,l+1) |
---|
280 | ncorecfm5 = ncorecfm5 + 1 |
---|
281 | ENDIF |
---|
282 | ENDDO |
---|
283 | ENDIF |
---|
284 | |
---|
285 | !------------------------------------------------------------------------------ |
---|
286 | ! Test detrainment inferieur au flux de masse |
---|
287 | !------------------------------------------------------------------------------ |
---|
288 | |
---|
289 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
290 | ! AB : Even if fm has no negative value, it can be lesser than detr. |
---|
291 | ! That's not suitable because when we will mix the plume with the |
---|
292 | ! environment, it will detrain more mass than it is physically able to do. |
---|
293 | ! When it occures, that imply that entr + fm is greater than detr, |
---|
294 | ! otherwise we get a negative outgoing mass flux (cf. above). |
---|
295 | ! That is why we correct the detrainment as follows. |
---|
296 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
297 | |
---|
298 | DO ig=1,ngrid |
---|
299 | IF (detr(ig,l).gt.fm(ig,l)) THEN |
---|
300 | detr(ig,l) = fm(ig,l) |
---|
301 | entr(ig,l) = fm(ig,l+1) |
---|
302 | |
---|
303 | IF (prt_level.ge.10) THEN |
---|
304 | print *, 'WARNING: Detrainment is modified in thermcell_flux!' |
---|
305 | print *, 'ig,l,lmax', ig, l, lmax(ig) |
---|
306 | ENDIF |
---|
307 | |
---|
308 | IF (prt_level.ge.100) THEN |
---|
309 | print *, 'fm-', fm(ig,l) |
---|
310 | print *, 'entr,detr', entr(ig,l), detr(ig,l) |
---|
311 | print *, 'fm+', fm(ig,l+1) |
---|
312 | ENDIF |
---|
313 | |
---|
314 | ncorecfm6 = ncorecfm6 + 1 |
---|
315 | |
---|
316 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
317 | ! Dans le cas ou on est au dessus de la couche d'alimentation et que le |
---|
318 | ! detrainement est plus fort que le flux de masse, on stope le thermique. |
---|
319 | ! test : on commente |
---|
320 | ! |
---|
321 | ! AB : Do we have to stop the plume here? |
---|
322 | ! AB : Attention, if lmax is modified, be sure that fm, zw2, entr and detr are |
---|
323 | ! set to zero above this level! |
---|
324 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
325 | ! IF (l.gt.lalim(ig)) THEN |
---|
326 | ! lmax(ig)=l |
---|
327 | ! fm(ig,l+1)=0. |
---|
328 | ! entr(ig,l)=0. |
---|
329 | ! ELSE |
---|
330 | ! ncorecfm2=ncorecfm2+1 |
---|
331 | ! ENDIF |
---|
332 | ENDIF |
---|
333 | ! |
---|
334 | ! IF (l.gt.lmax(ig)) THEN |
---|
335 | ! detr(ig,l) = 0. |
---|
336 | ! fm(ig,l+1) = 0. |
---|
337 | ! entr(ig,l) = 0. |
---|
338 | ! ENDIF |
---|
339 | ENDDO |
---|
340 | |
---|
341 | ! labort_physic=.false. |
---|
342 | ! |
---|
343 | ! DO ig=1,ngrid |
---|
344 | ! IF (entr(ig,l).lt.0.) THEN |
---|
345 | ! labort_physic=.true. |
---|
346 | ! igout=ig |
---|
347 | ! ENDIF |
---|
348 | ! ENDDO |
---|
349 | ! |
---|
350 | ! IF (labort_physic) THEN |
---|
351 | ! print *, 'ERROR: detrainment is greater than mass flux and' |
---|
352 | ! print *, ' entrainment cannot compensate it!' |
---|
353 | ! print *, 'ig,l,lmax(ig)', igout, l, lmax(igout) |
---|
354 | ! print *, '--------------------' |
---|
355 | ! print *, 'fm+', fm(igout,lout+1) |
---|
356 | ! print *, 'entr,detr', entr(igout,lout), detr(igout,lout) |
---|
357 | ! print *, 'fm-', fm(igout,lout) |
---|
358 | ! abort_message = 'problem in thermcell_flux' |
---|
359 | ! CALL abort_physic (modname,abort_message,1) |
---|
360 | ! ENDIF |
---|
361 | |
---|
362 | !------------------------------------------------------------------------------ |
---|
363 | ! Test fraction masse entrainee inferieure a fomass_max |
---|
364 | !------------------------------------------------------------------------------ |
---|
365 | |
---|
366 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
367 | ! AB : Entrainment is bigger than the maximal authorized value. |
---|
368 | ! If we consider that the excess entrainement is in fact plume air which |
---|
369 | ! is not detrained then we compensate it by decreasing detr. |
---|
370 | ! If it's not enough, we can increase entr in the layer above and decrease |
---|
371 | ! the outgoing mass flux in the current layer. |
---|
372 | ! If it's still unsufficient, code will abort (now commented). |
---|
373 | ! Else we reset entr to its intial value and we renormalize entrainment, |
---|
374 | ! detrainment and mass flux profiles such as we do not exceed the maximal |
---|
375 | ! authorized entrained mass. |
---|
376 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
377 | |
---|
378 | labort_physic=.false. |
---|
379 | |
---|
380 | DO ig=1,ngrid |
---|
381 | eee0 = entr(ig,l) |
---|
382 | ddd0 = detr(ig,l) |
---|
383 | eee = entr(ig,l) - masse(ig,l) * fomass_max / ptimestep |
---|
384 | ddd = detr(ig,l) - eee |
---|
385 | |
---|
386 | IF (eee.gt.0.) THEN |
---|
387 | entr(ig,l) = entr(ig,l) - eee |
---|
388 | ncorecfm3 = ncorecfm3 + 1 |
---|
389 | |
---|
390 | IF (prt_level.ge.10) THEN |
---|
391 | print *, 'WARNING: Entrainment is modified in thermcell_flux!' |
---|
392 | print *, 'ig,l,lmax', ig, l, lmax(ig) |
---|
393 | ENDIF |
---|
394 | |
---|
395 | IF (ddd.gt.0.) THEN ! on reduit le detr dans la couche |
---|
396 | detr(ig,l) = ddd |
---|
397 | ELSEIF (l.eq.lmax(ig)) THEN ! on ajuste le detr dans la couche |
---|
398 | detr(ig,l) = fm(ig,l) + entr(ig,l) |
---|
399 | ELSEIF (entr(ig,l+1).gt.ABS(ddd)) THEN ! on reduit le detr dans la couche et l'entr au-dessus |
---|
400 | detr(ig,l) = 0. |
---|
401 | fm(ig,l+1) = fm(ig,l) + entr(ig,l) |
---|
402 | entr(ig,l+1) = entr(ig,l+1) + ddd |
---|
403 | ! ELSE |
---|
404 | ! entr(ig,l) = entr(ig,l) + eee |
---|
405 | ! igout=ig |
---|
406 | ! lout=l |
---|
407 | ! labort_physic=.true. |
---|
408 | ELSE |
---|
409 | fact = (eee0 - eee) / eee0 |
---|
410 | entr(ig,l) = eee0 |
---|
411 | detr(ig,:) = detr(ig,:) * fact |
---|
412 | entr(ig,:) = entr(ig,:) * fact |
---|
413 | fm(ig,:) = fm(ig,:) * fact |
---|
414 | |
---|
415 | IF (prt_level.ge.1) THEN |
---|
416 | print *, 'WARNING: Normalisation is modified in thermcell_flux!' |
---|
417 | print *, 'old f, new f :', f(ig), fact * f(ig) |
---|
418 | ENDIF |
---|
419 | ENDIF |
---|
420 | ENDIF |
---|
421 | ENDDO |
---|
422 | |
---|
423 | IF (labort_physic) THEN |
---|
424 | print *, 'ERROR: Entrainment is greater than its maximal authorized value!' |
---|
425 | print *, ' Nor detrainment neither entrainment can compensate it!' |
---|
426 | print *, 'ig,l,entr', igout, lout, entr(igout,lout) |
---|
427 | print *, 'lmin,lmax', lmin(igout), lmax(igout) |
---|
428 | print *, '--------------------' |
---|
429 | print *, 'e_max :', masse(igout,lout)*fomass_max/ptimestep |
---|
430 | print *, ' fomass_max :', fomass_max |
---|
431 | print *, ' masse :', masse(igout,lout) |
---|
432 | print *, ' ptimestep :', ptimestep |
---|
433 | print *, 'norm :', f(igout) |
---|
434 | print *, 'alim* :', alim_star(igout,lout) |
---|
435 | print *, 'entr* :', entr_star(igout,lout) |
---|
436 | print *, '--------------------' |
---|
437 | print *, 'fm l+1 ', fm(igout,lout+2) |
---|
438 | print *, 'entr <-- ', entr(igout,lout+1) |
---|
439 | print *, 'detr -->', detr(igout,lout+1) |
---|
440 | print *, 'fm l ', fm(igout,lout+1) |
---|
441 | print *, 'entr <-- ', entr(igout,lout) |
---|
442 | print *, 'detr -->', detr(igout,lout) |
---|
443 | print *, 'fm l-1 ', fm(igout,lout) |
---|
444 | call flush |
---|
445 | abort_message = 'problem in thermcell_flux' |
---|
446 | CALL abort_physic (modname,abort_message,1) |
---|
447 | ENDIF |
---|
448 | |
---|
449 | !------------------------------------------------------------------------------ |
---|
450 | ! Test fraction couverte inferieure a alphamax |
---|
451 | !------------------------------------------------------------------------------ |
---|
452 | |
---|
453 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
454 | ! FH : Partie a revisiter. |
---|
455 | ! Il semble qu'etaient codees ici deux optiques dans le cas F/(rho*w) > 1 |
---|
456 | ! - soit limiter la hauteur du thermique en considerant que c'est |
---|
457 | ! la derniere chouche |
---|
458 | ! - soit limiter F a rho w. |
---|
459 | ! Dans le second cas, il faut en fait limiter a un peu moins que ca parce |
---|
460 | ! qu'on a des 1/(1-alpha) un peu plus loin dans thermcell_main et qu'il |
---|
461 | ! semble de toutes facons deraisonable d'avoir des fractions de 1... |
---|
462 | ! Ci-dessous, et dans l'etat actuel, le premier des deux if est sans doute inutile. |
---|
463 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
464 | |
---|
465 | DO ig=1,ngrid |
---|
466 | zfm = rhobarz(ig,l+1) * zw2(ig,l+1) * alphamax |
---|
467 | IF (fm(ig,l+1) .gt. zfm) THEN |
---|
468 | f_old = fm(ig,l+1) |
---|
469 | fm(ig,l+1) = zfm |
---|
470 | detr(ig,l) = detr(ig,l) + f_old - fm(ig,l+1) |
---|
471 | |
---|
472 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
473 | ! AB : The previous change doesn't observe the equation df/dz = e - d. |
---|
474 | ! To avoid this issue, what is better to do? I choose to increase the |
---|
475 | ! entrainment in the layer above when l<lmax. If l=lmax then fm(l+1)=0 and |
---|
476 | ! there are never any problems. |
---|
477 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
478 | IF (l.lt.lmax(ig)) THEN |
---|
479 | entr(ig,l+1) = entr(ig,l+1) + f_old - fm(ig,l+1) |
---|
480 | ENDIF |
---|
481 | |
---|
482 | IF (prt_level.ge.10) THEN |
---|
483 | print *, 'Mass flux is modified in thermcell_flux' |
---|
484 | print *, 'ig,l,lmax', ig, l, lmax(ig) |
---|
485 | ENDIF |
---|
486 | |
---|
487 | IF (prt_level.ge.100) THEN |
---|
488 | print *, 'fm-', fm(ig,l) |
---|
489 | print *, 'entr,detr', entr(ig,l), detr(ig,l) |
---|
490 | print *, 'fm+', fm(ig,l+1) |
---|
491 | ENDIF |
---|
492 | |
---|
493 | ncorecalpha = ncorecalpha + 1 |
---|
494 | |
---|
495 | ENDIF |
---|
496 | ENDDO |
---|
497 | |
---|
498 | ENDDO |
---|
499 | |
---|
500 | !------------------------------------------------------------------------------ |
---|
501 | ! We check if fm, entr and detr vanish correctly in layer lmax |
---|
502 | !------------------------------------------------------------------------------ |
---|
503 | |
---|
504 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
505 | ! AB : test added to avoid problem when lmax = 0, which is not a fortran index. |
---|
506 | ! Theoretically, we always get lmax >= lmin >= linf > 0 |
---|
507 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
508 | DO ig=1,ngrid |
---|
509 | IF (lmax(ig).gt.0) THEN |
---|
510 | detr(ig,lmax(ig)) = fm(ig,lmax(ig)) + entr(ig,lmax(ig)) |
---|
511 | fm(ig,lmax(ig)+1) = 0. |
---|
512 | entr(ig,lmax(ig)) = 0. |
---|
513 | ENDIF |
---|
514 | ENDDO |
---|
515 | |
---|
516 | !------------------------------------------------------------------------------ |
---|
517 | ! Impression des bidouilles utilisees pour corriger les problemes |
---|
518 | !------------------------------------------------------------------------------ |
---|
519 | |
---|
520 | IF (prt_level.ge.1) THEN |
---|
521 | |
---|
522 | IF (ncorecfm4.ge.1) THEN |
---|
523 | print *, 'WARNING: Deacreasing updraft fraction above lalim!' |
---|
524 | print *, 'in', ncorecfm4, 'point(s)' |
---|
525 | ENDIF |
---|
526 | |
---|
527 | IF (ncorecfm5.ge.1) THEN |
---|
528 | print *, 'WARNING: Increasing mass flux above lalim!' |
---|
529 | print *, 'in', ncorecfm5, 'point(s)' |
---|
530 | ENDIF |
---|
531 | |
---|
532 | IF (ncorecfm6.ge.1) THEN |
---|
533 | print *, 'WARNING: Detrainment is greater than mass flux!' |
---|
534 | print *, 'in', ncorecfm6, 'point(s)' |
---|
535 | ENDIF |
---|
536 | |
---|
537 | ! AB : those outputs are commented because corresponding test is also commented. |
---|
538 | ! IF (ncorecfm2.ge.1) THEN |
---|
539 | ! print *, 'WARNING: Detrainment is greater than mass flux!' |
---|
540 | ! print *, 'in', ncorecfm2, 'point(s)' |
---|
541 | ! ENDIF |
---|
542 | |
---|
543 | IF (ncorecfm3.ge.1) THEN |
---|
544 | print *, 'WARNING: Entrained mass is greater than maximal authorized value!' |
---|
545 | print *, 'in', ncorecfm3, 'point(s)' |
---|
546 | ENDIF |
---|
547 | |
---|
548 | IF (ncorecalpha.ge.1) THEN |
---|
549 | print *, 'WARNING: Updraft fraction is greater than maximal authorized value!' |
---|
550 | print *, 'in', ncorecalpha, 'point(s)' |
---|
551 | ENDIF |
---|
552 | |
---|
553 | ENDIF |
---|
554 | |
---|
555 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
556 | ! AB : temporary test added to check the validity of eq. df/dz = e - d |
---|
557 | !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ |
---|
558 | ! DO l=1,nlay |
---|
559 | ! DO ig=1,ngrid |
---|
560 | ! test = abs(fm(ig,l) + entr(ig,l) - detr(ig,l) - fm(ig,l+1)) |
---|
561 | ! IF (test.gt.1.e-10) THEN |
---|
562 | ! print *, 'WARNING: df/dz != entr - detr' |
---|
563 | ! print *, 'ig,l', ig, l |
---|
564 | ! print *, 'fm+ :', fm(ig,l+1) |
---|
565 | ! print *, 'entr,detr', entr(ig,l), detr(ig,l) |
---|
566 | ! print *, 'fm :', fm(ig,l) |
---|
567 | ! print *, 'entr,detr', entr(ig,l-1), detr(ig,l-1) |
---|
568 | ! print *, 'fm- :', fm(ig,l-1) |
---|
569 | ! print *, 'err. :', test |
---|
570 | ! ENDIF |
---|
571 | ! ENDDO |
---|
572 | ! ENDDO |
---|
573 | |
---|
574 | |
---|
575 | RETURN |
---|
576 | END |
---|