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

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

Fix in convadj.F
New version of the thermal plume model (new entrainment and detrainment formulae, alimentation is removed)

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