source: trunk/LMDZ.GENERIC/libf/phystd/thermcell_flux.F90 @ 2132

Last change on this file since 2132 was 2132, checked in by aboissinot, 6 years ago

Alimentation (more precisely lalim) is removed from thermcell_flux as well as corrections which need it.
Consequently, iflag_thermals_optflux flag is removed from thermcell_mod.

File size: 18.3 KB
Line 
1!
2!
3!
4SUBROUTINE thermcell_flux(ngrid,nlay,ptimestep,masse,                         &
5                          lmin,lmax,entr_star,detr_star,                      &
6                          f,rhobarz,zlev,zw2,fm,entr,detr,zqla)
7     
8     
9!===============================================================================
10!  Purpose: fluxes deduction
11
12!  Modif 2019/04 (AB alexandre.boissinot@lmd.jussieu.fr)
13
14!===============================================================================
15     
16      USE print_control_mod, ONLY: prt_level
17      USE thermcell_mod, ONLY: fomass_max, alpha_max
18     
19      IMPLICIT NONE
20     
21     
22!===============================================================================
23! Declaration
24!===============================================================================
25     
26!     Inputs:
27!     -------
28     
29      INTEGER ngrid, nlay
30      INTEGER lmin(ngrid)
31      INTEGER lmax(ngrid)
32     
33      REAL entr_star(ngrid,nlay)
34      REAL detr_star(ngrid,nlay)
35      REAL zw2(ngrid,nlay+1)
36      REAL zlev(ngrid,nlay+1)
37      REAL masse(ngrid,nlay)
38      REAL ptimestep
39      REAL rhobarz(ngrid,nlay)
40      REAL f(ngrid)
41      REAL zqla(ngrid,nlay)
42      REAL zmax(ngrid)
43     
44!     Outputs:
45!     --------     
46     
47      REAL entr(ngrid,nlay)
48      REAL detr(ngrid,nlay)
49      REAL fm(ngrid,nlay+1)
50     
51!     Local:
52!     ------
53     
54      INTEGER ig, l, k
55      INTEGER igout, lout                 ! Error grid point number and level
56     
57      REAL zfm                            ! Mass flux such as updraft fraction is equal to its maximal authorized value alpha_max
58      REAL f_old                          ! Save initial value of mass flux
59      REAL eee0                           ! Save initial value of entrainment
60      REAL ddd0                           ! Save initial value of detrainment
61      REAL eee                            ! eee0 - layer mass * maximal authorized mass fraction / dt
62      REAL ddd                            ! ddd0 - eee
63      REAL zzz                            ! Temporary variable set to mass flux
64      REAL fact                           ! Factor between old norm and new norm
65     
66      INTEGER ncorecdetr                  ! detr > fm-   counter
67      INTEGER ncorecentr                  ! entr > e_max counter
68      INTEGER ncorecalpha                 ! fm > zfm     counter
69     
70      LOGICAL labort_physic
71     
72      CHARACTER (len=20) :: modname='thermcell_flux'
73      CHARACTER (len=80) :: abort_message
74     
75!===============================================================================
76! Initialization
77!===============================================================================
78     
79      ncorecdetr  = 0
80      ncorecentr  = 0
81      ncorecalpha = 0
82     
83      entr(:,:) = 0.
84      detr(:,:) = 0.
85      fm(:,:)   = 0.
86     
87!===============================================================================
88! Mass flux, entrainment and detrainment
89!===============================================================================
90     
91!-------------------------------------------------------------------------------
92! Multiplication par la norme issue de la relation de fermeture
93!-------------------------------------------------------------------------------
94     
95      DO l=1,nlay
96         entr(:,l) = f(:) * entr_star(:,l)
97         detr(:,l) = f(:) * detr_star(:,l)
98      ENDDO
99     
100!-------------------------------------------------------------------------------
101! Mass flux and boundary conditions
102!-------------------------------------------------------------------------------
103     
104      DO l=1,nlay
105         DO ig=1,ngrid
106            IF (l.lt.lmax(ig) .and. l.ge.lmin(ig)) THEN
107               fm(ig,l+1) = fm(ig,l) + entr(ig,l) - detr(ig,l)
108            ELSEIF (l.eq.lmax(ig)) THEN
109               fm(ig,l+1) = 0.
110               detr(ig,l) = fm(ig,l) + entr(ig,l)
111            ELSE
112               fm(ig,l+1) = 0.
113               entr(ig,l) = 0.
114               detr(ig,l) = 0.
115            ENDIF
116         ENDDO
117      ENDDO
118     
119!===============================================================================
120! Validity tests and corrections
121!===============================================================================
122     
123      DO l=1,nlay
124         
125!-------------------------------------------------------------------------------
126! Is incoming mass flux positive ?
127!-------------------------------------------------------------------------------
128         
129!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
130! AB : I remove the correction and replace it by an uncompromising test.
131!      According to the previous derivations, we MUST have positive mass flux
132!      everywhere! Indeed, as soon as fm becomes negative, the plume stops.
133!      Then the only value which can be negative is the mass flux at the top of
134!      the plume. However, this value was set to zero a few lines above.
135!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
136         
137         labort_physic=.false.
138         
139         DO ig=1,ngrid
140            IF (fm(ig,l).lt.0.) THEN
141               labort_physic = .true.
142               igout = ig
143               lout = l
144            ENDIF
145         ENDDO
146         
147         IF (labort_physic) THEN
148            print *, 'ERROR: mass flux has negative value(s)!'
149            print *, 'ig,l,fm',igout, lout, fm(igout,lout)
150            print *, 'lmin,lmax', lmin(igout), lmax(igout)
151            print *, '-------------------------------'
152            DO k=nlay,1,-1
153               print *, 'fm ', fm(igout,k+1)
154               print *, 'entr,detr', entr(igout,k), detr(igout,k)
155            ENDDO
156            print *, 'fm-', fm(igout,1)
157            print *, '-------------------------------'
158            abort_message = 'Negative incoming fm in thermcell_flux'
159            CALL abort_physic(modname,abort_message,1)
160         ENDIF
161         
162!-------------------------------------------------------------------------------
163! Is entrainment positive ?
164!-------------------------------------------------------------------------------
165         
166!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
167! AB : According to the previous derivations, we MUST have positive entrainment
168!      and detrainment everywhere!
169!      Indeed, they are set to max between zero and a computed value.
170!      Then tests are uncompromising.
171!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
172         
173         DO ig=1,ngrid
174            IF (entr(ig,l).lt.0.) THEN
175               labort_physic = .true.
176               igout = ig
177               lout = l
178            ENDIF
179         ENDDO
180         
181         IF (labort_physic) THEN
182            print *, 'ERROR: entrainment has negative value(s)!'
183            print *, 'ig,l,entr', igout, lout, entr(igout,lout)
184            print *, 'lmin,lmax', lmin(igout), lmax(igout)
185            print *, '-------------------------------'
186            DO k=nlay,1,-1
187               print *, 'fm ', fm(igout,k+1)
188               print *, 'entr,detr', entr(igout,k), detr(igout,k)
189            ENDDO
190            print *, 'fm ', fm(igout,1)
191            print *, '-------------------------------'
192            abort_message = 'Negative entrainment in thermcell_flux'
193            CALL abort_physic(modname,abort_message,1)
194         ENDIF
195         
196!-------------------------------------------------------------------------------
197! Is detrainment positive ?
198!-------------------------------------------------------------------------------
199         
200         DO ig=1,ngrid
201            IF (detr(ig,l).lt.0.) THEN
202               labort_physic = .true.
203               igout = ig
204               lout = l
205            ENDIF
206         ENDDO
207         
208         IF (labort_physic) THEN
209            print *, 'ERROR: detrainment has negative value(s)!'
210            print *, 'ig,l,detr', igout, lout, detr(igout,lout)
211            print *, 'lmin,lmax', lmin(igout), lmax(igout)
212            print *, '-------------------------------'
213            DO k=nlay,1,-1
214               print *, 'fm ', fm(igout,k+1)
215               print *, 'entr,detr', entr(igout,k), detr(igout,k)
216            ENDDO
217            print *, 'fm ', fm(igout,1)
218            print *, '-------------------------------'
219            abort_message = 'Negative detrainment in thermcell_flux'
220            CALL abort_physic(modname,abort_message,1)
221         ENDIF
222         
223!-------------------------------------------------------------------------------
224! Is detrainment lesser than incoming mass flux ?
225!-------------------------------------------------------------------------------
226         
227!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
228! AB : Even if fm has no negative value, it can be lesser than detr.
229!      That's not suitable because when we will mix the plume with the
230!      environment, it will detrain more mass than it is physically able to do.
231!      When it occures, that imply that entr + fm is greater than detr,
232!      otherwise we get a negative outgoing mass flux (cf. above).
233!      That is why we correct the detrainment as follows.
234!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
235         
236         DO ig=1,ngrid
237            IF (detr(ig,l).gt.fm(ig,l)) THEN
238               detr(ig,l) = fm(ig,l)
239               entr(ig,l) = fm(ig,l+1)
240               
241               IF (prt_level.ge.10) THEN
242                  print *, 'WARNING: Detrainment is modified in thermcell_flux!'
243                  print *, 'ig,l,lmax', ig, l, lmax(ig)
244               ENDIF
245               
246               IF (prt_level.ge.100) THEN
247                  print *, 'fm+', fm(ig,l+1)
248                  print *, 'entr,detr', entr(ig,l), detr(ig,l)
249                  print *, 'fm-', fm(ig,l)
250               ENDIF
251               
252               ncorecdetr  = ncorecdetr + 1
253               
254            ENDIF
255         ENDDO
256         
257!-------------------------------------------------------------------------------
258! Is entrainment mass fraction lesser than fomass_max ?
259!-------------------------------------------------------------------------------
260         
261!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
262! AB : Entrainment is bigger than the maximal authorized value.
263!      If we consider that the excess entrainement is in fact plume air which
264!      is not detrained then we compensate it by decreasing detr.
265!      If it's not enough, we can increase entr in the layer above and decrease
266!      the outgoing mass flux in the current layer.
267!      If it's still unsufficient, code will abort (now commented).
268!      Else we reset entr to its intial value and we renormalize entrainment,
269!      detrainment and mass flux profiles such as we do not exceed the maximal
270!      authorized entrained mass.
271!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
272         
273         labort_physic=.false.
274         
275         DO ig=1,ngrid
276            eee0 = entr(ig,l)
277            ddd0 = detr(ig,l)
278            eee  = entr(ig,l) - masse(ig,l) * fomass_max / ptimestep
279            ddd  = detr(ig,l) - eee
280           
281            IF (eee.gt.0.) THEN
282               entr(ig,l) = entr(ig,l) - eee
283               ncorecentr  = ncorecentr + 1
284               
285               IF (prt_level.ge.10) THEN
286                  print *, 'WARNING: Entrainment is modified in thermcell_flux!'
287                  print *, 'ig,l,lmax', ig, l, lmax(ig)
288               ENDIF
289               
290               IF (ddd.gt.0.) THEN                          ! detr in the current layer is reduced
291                  detr(ig,l) = ddd
292               ELSEIF (l.eq.lmax(ig)) THEN                  ! detr in the last layer is adjusted
293                  detr(ig,l) = fm(ig,l) + entr(ig,l)
294               ELSEIF (entr(ig,l+1).gt.ABS(ddd)) THEN       ! detr in the current layer is set to 0 and entr in the layer above is reduced
295                  detr(ig,l) = 0.
296                  fm(ig,l+1) = fm(ig,l) + entr(ig,l)
297                  entr(ig,l+1) = entr(ig,l+1) + ddd
298!               ELSE
299!                  entr(ig,l) = entr(ig,l) + eee
300!                  igout=ig
301!                  lout=l
302!                  labort_physic=.true.
303               ELSE
304                  fact = (eee0 - eee) / eee0
305                  entr(ig,l) = eee0
306                  detr(ig,:) = detr(ig,:) * fact
307                  entr(ig,:) = entr(ig,:) * fact
308                  fm(ig,:)   = fm(ig,:) * fact
309                 
310                  IF (prt_level.ge.1) THEN
311                     print *, 'WARNING: Normalisation is modified in thermcell_flux!'
312                     print *, 'old f, new f :', f(ig), fact * f(ig)
313                  ENDIF
314               ENDIF
315            ENDIF
316         ENDDO
317         
318!         IF (labort_physic) THEN
319!            print *, 'ERROR: Entrainment is greater than its maximal authorized value!'
320!            print *, '       Nor detrainment neither entrainment can compensate it!'
321!            print *, 'ig,l,entr', igout, lout, entr(igout,lout)
322!            print *, 'lmin,lmax', lmin(igout), lmax(igout)
323!            print *, '--------------------'
324!            print *, 'e_max :', masse(igout,lout)*fomass_max/ptimestep
325!            print *, '   fomass_max :', fomass_max
326!            print *, '   masse      :', masse(igout,lout)
327!            print *, '   ptimestep  :', ptimestep
328!            print *, 'norm  :', f(igout)
329!            print *, 'entr* :', entr_star(igout,lout)
330!            print *, '--------------------'
331!            DO k=nlay,1,-1
332!               print *, 'fm ', fm(igout,k+1)
333!               print *, 'entr,detr', entr(igout,k), detr(igout,k)
334!            ENDDO
335!            print *, 'fm ', fm(igout,1)
336!            print *, '-------------------------------'
337!            abort_message = 'Entrainment is too large in thermcell_flux'
338!            CALL abort_physic (modname,abort_message,1)
339!         ENDIF
340         
341!-------------------------------------------------------------------------------
342! Is updraft fraction lesser than alpha_max ?
343!-------------------------------------------------------------------------------
344         
345!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
346! FH : Partie a revisiter.
347!      Il semble qu'etaient codees ici deux optiques dans le cas F/(rho*w) > 1
348!      - soit limiter la hauteur du thermique en considerant que c'est
349!        la derniere chouche
350!      - soit limiter F a rho w.
351!      Dans le second cas, il faut en fait limiter a un peu moins que ca parce
352!      qu'on a des 1/(1-alpha) un peu plus loin dans thermcell_main et qu'il
353!      semble de toutes facons deraisonable d'avoir des fractions de 1...
354!      Ci-dessous, et dans l'etat actuel, le premier des deux if est sans doute inutile. 
355!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~                 
356         
357         DO ig=1,ngrid
358            zfm = rhobarz(ig,l+1) * zw2(ig,l+1) * alpha_max
359           
360            IF (fm(ig,l+1) .gt. zfm) THEN
361               f_old = fm(ig,l+1)
362               fm(ig,l+1) = zfm
363               detr(ig,l) = detr(ig,l) + f_old - fm(ig,l+1)
364               
365!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
366! AB : The previous change doesn't observe the equation df/dz = e - d.
367!      To avoid this issue, what is better to do? I choose to increase the
368!      entrainment in the layer above when l<lmax. If l=lmax then fm(l+1)=0 and
369!      there are never any problems.
370!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
371               IF (l.lt.lmax(ig)) THEN
372                  entr(ig,l+1) = entr(ig,l+1) + f_old - fm(ig,l+1)
373               ENDIF
374               
375               IF (prt_level.ge.10) THEN
376                  print *, 'Mass flux is modified in thermcell_flux'
377                  print *, 'ig,l,lmax', ig, l, lmax(ig)
378               ENDIF
379               
380               IF (prt_level.ge.100) THEN
381                  print *, 'fm-', fm(ig,l)
382                  print *, 'entr,detr', entr(ig,l), detr(ig,l)
383                  print *, 'fm+', fm(ig,l+1)
384               ENDIF
385               
386               ncorecalpha = ncorecalpha + 1
387            ENDIF
388         ENDDO
389         
390      ENDDO
391     
392!-------------------------------------------------------------------------------
393! Boundary conditions
394!-------------------------------------------------------------------------------
395     
396!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
397! AB : test added to avoid problem when lmax = 0, which is not a fortran index.
398!      Theoretically, we always get lmax >= lmin >= linf > 0
399!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
400      DO ig=1,ngrid
401         IF (lmax(ig).gt.0) THEN
402            detr(ig,lmax(ig)) = fm(ig,lmax(ig)) + entr(ig,lmax(ig))
403            fm(ig,lmax(ig)+1) = 0.
404            entr(ig,lmax(ig)) = 0.
405         ENDIF
406      ENDDO
407     
408!-------------------------------------------------------------------------------
409! Corrections display
410!-------------------------------------------------------------------------------
411     
412      IF (prt_level.GE.1) THEN
413                 
414         IF (ncorecdetr.GE.1) THEN
415            print *, 'WARNING: Detrainment is greater than mass flux!'
416            print *, '         In', ncorecdetr, 'point(s)'
417         ENDIF
418         
419         IF (ncorecentr.GE.1) THEN
420            print *, 'WARNING: Entrained mass is greater than maximal authorized value!'
421            print *, '         In', ncorecentr, 'point(s)'
422         ENDIF
423         
424         IF (ncorecalpha.GE.1) THEN
425            print *, 'WARNING: Updraft fraction is greater than maximal authorized value!'
426            print *, '         In', ncorecalpha, 'point(s)'
427         ENDIF
428         
429      ENDIF
430     
431! AB : temporary test added to check the validity of eq. df/dz = e - d
432!      DO l=1,nlay
433!         DO ig=1,ngrid
434!            test = abs(fm(ig,l) + entr(ig,l) - detr(ig,l) - fm(ig,l+1))
435!            IF (test.gt.1.e-10) THEN
436!               print *, 'WARNING: df/dz != entr - detr'
437!               print *, 'ig,l', ig, l
438!               print *, 'fm+  :', fm(ig,l+1)
439!               print *, 'entr,detr', entr(ig,l), detr(ig,l)
440!               print *, 'fm   :', fm(ig,l)
441!               print *, 'entr,detr', entr(ig,l-1), detr(ig,l-1)
442!               print *, 'fm-  :', fm(ig,l-1)
443!               print *, 'err. :', test
444!            ENDIF
445!         ENDDO
446!      ENDDO
447     
448     
449RETURN
450END
Note: See TracBrowser for help on using the repository browser.