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

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

Uncomment two "corrections" (or "bidouilles" ccording to the author) in thermcell_flux. They are used only if
iflag_thermals_optflux is set to 0

Remove useless parameter fact_shell in thermcell_mod.

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