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

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

Fix a bug in thermcell_alim.F90 where vertical and horizontal loops must be inverted.
In thermal plume model, arrays size declaration is standardised (no longer done thanks to dimphy module but by way of arguments).
Clean up some thermal plume model routines (remove uselesss variables...)

File size: 21.7 KB
Line 
1!
2!
3!
4SUBROUTINE 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
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,nlay
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,nlay
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,nlay
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         
189! AB : Do we have to decree that? If so, set iflag_thermals_optflux to 0
190         IF (iflag_thermals_optflux==0) THEN
191            DO ig=1,ngrid
192               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
193                  zzz = fm(ig,l) * rhobarz(ig,l+1) * zw2(ig,l+1)              &
194                  &   / (rhobarz(ig,l) * zw2(ig,l))
195                 
196                  IF (fm(ig,l+1).gt.zzz) THEN
197                     detr(ig,l) = detr(ig,l) + fm(ig,l+1) - zzz
198                     fm(ig,l+1) = zzz
199                     ncorecfm4  = ncorecfm4 + 1
200                  ENDIF
201               ENDIF
202            ENDDO
203         ENDIF
204         
205!------------------------------------------------------------------------------
206! Test sur flux de masse constant ou decroissant au-dessus de lalim
207!------------------------------------------------------------------------------
208         
209! AB : Do we have to decree that? If so, set iflag_thermals_optflux to 0
210         IF (iflag_thermals_optflux==0) THEN
211            DO ig=1,ngrid
212               IF ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
213                  f_old = fm(ig,l+1)
214                  fm(ig,l+1) = fm(ig,l)
215                  detr(ig,l) = detr(ig,l) + f_old - fm(ig,l+1)
216                  ncorecfm5  = ncorecfm5 + 1
217               ENDIF
218            ENDDO
219         ENDIF
220         
221!------------------------------------------------------------------------------
222! Test entrainment et detrainment positif
223!------------------------------------------------------------------------------
224         
225!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
226! AB : According to the previous derivations, we MUST have positive entrainment
227!      and detrainment everywhere!
228!      Indeed, they are set to max between zero and a computed value.
229!      Then tests are uncompromising.
230!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
231         
232         labort_physic=.false.
233         
234         DO ig=1,ngrid
235            IF (entr(ig,l).lt.0.) THEN
236               labort_physic = .true.
237               igout = ig
238               lout = l
239            ENDIF
240         ENDDO
241         
242         IF (labort_physic) THEN
243            print *, 'ERROR: entrainment has negative value(s)!'
244            print *, 'ig,l,entr', igout, lout, entr(igout,lout)
245            abort_message = 'negative entrainment in thermcell_flux'
246            CALL abort_physic(modname,abort_message,1)
247         ENDIF
248         
249         DO ig=1,ngrid
250            IF (detr(ig,l).lt.0.) THEN
251               labort_physic = .true.
252               igout = ig
253               lout = l
254            ENDIF
255         ENDDO
256         
257         IF (labort_physic) THEN
258            print *, 'ERROR: detrainment has negative value(s)!'
259            print *, 'ig,l,detr', igout, lout, detr(igout,lout)
260            abort_message = 'negative detrainment in thermcell_flux'
261            CALL abort_physic(modname,abort_message,1)
262         ENDIF
263         
264!------------------------------------------------------------------------------
265! Test detrainment inferieur au flux de masse
266!------------------------------------------------------------------------------
267         
268!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
269! AB : Even if fm has no negative value, it can be lesser than detr.
270!      That's not suitable because when we will mix the plume with the
271!      environment, it will detrain more mass than it is physically able to do.
272!      When it occures, that imply that entr + fm is greater than detr,
273!      otherwise we get a negative outgoing mass flux (cf. above).
274!      That is why we correct the detrainment as follows.
275!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
276         
277         DO ig=1,ngrid
278            IF (detr(ig,l).gt.fm(ig,l)) THEN
279               detr(ig,l) = fm(ig,l)
280               entr(ig,l) = fm(ig,l+1)
281               
282               IF (prt_level.ge.10) THEN
283                  print *, 'Detrainment is modified in thermcell_flux'
284                  print *, 'ig,l,lmax', ig, l, lmax(ig)
285               ENDIF
286               
287               IF (prt_level.ge.100) THEN
288                  print *, 'fm-', fm(ig,l)
289                  print *, 'entr,detr', entr(ig,l), detr(ig,l)
290                  print *, 'fm+', fm(ig,l+1)
291               ENDIF
292               
293               ncorecfm6  = ncorecfm6 + 1
294               
295!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
296! Dans le cas ou on est au dessus de la couche d'alimentation et que le
297! detrainement est plus fort que le flux de masse, on stope le thermique.
298! test : on commente
299!
300! AB : Do we have to stop the plume here?
301!
302! AB : WARNING: if lmax is modified, be sure that fm, zw2, entr and detr are
303!      set to zero above this level!
304!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
305!               IF (l.gt.lalim(ig)) THEN
306!                  lmax(ig)=l
307!                  fm(ig,l+1)=0.
308!                  entr(ig,l)=0.
309!               ELSE
310!                  ncorecfm7=ncorecfm7+1
311!               ENDIF
312            ENDIF
313!           
314!            IF (l.gt.lmax(ig)) THEN
315!               detr(ig,l) = 0.
316!               fm(ig,l+1) = 0.
317!               entr(ig,l) = 0.
318!            ENDIF
319         ENDDO
320         
321!         labort_physic=.false.
322!         
323!         DO ig=1,ngrid
324!            IF (entr(ig,l).lt.0.) THEN
325!               labort_physic=.true.
326!               igout=ig
327!            ENDIF
328!         ENDDO
329!         
330!         IF (labort_physic) THEN
331!            print *, 'ERROR: detrainment is greater than mass flux and'
332!            print *, '       entrainment cannot compensate it!'
333!            print *, 'ig,l,lmax(ig)', igout, l, lmax(igout)
334!            print *, 'entr(ig,l)', entr(igout,l)
335!            print *, 'fm(ig,l)', fm(igout,l)
336!            abort_message = 'problem in thermcell_flux'
337!            CALL abort_physic (modname,abort_message,1)
338!         ENDIF
339         
340!------------------------------------------------------------------------------
341! Test fraction masse entrainee inferieure a fomass_max
342!------------------------------------------------------------------------------
343         
344!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
345! AB : Entrainment is bigger than the maximal authorized value.
346!      If we consider that the excess entrainement is in fact plume air which
347!      is not detrained then we compensate it by decreasing detr.
348!      If it's not enough, we can increase entr in the layer above and decrease
349!      the outgoing mass flux in the current layer.
350!      If it's still unsufficient, code will abort.
351!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
352         
353         labort_physic=.false.
354         
355         DO ig=1,ngrid
356            eee0 = entr(ig,l)
357            ddd0 = detr(ig,l)
358            eee  = entr(ig,l) - masse(ig,l) * fomass_max / ptimestep
359            ddd  = detr(ig,l) - eee
360           
361            IF (eee.gt.0.) THEN
362               entr(ig,l) = entr(ig,l) - eee
363               ncorecfm3  = ncorecfm3 + 1
364               
365               print *, 'CORRECTION: entr is to large!'
366               print *, 'ig,l,lmax', ig, l, lmax(ig)
367               
368               IF (ddd.gt.0.) THEN
369                  detr(ig,l) = ddd
370               ELSE
371                  IF (l.eq.lmax(ig)) THEN
372                     detr(ig,l) = fm(ig,l) + entr(ig,l)
373                  ELSEIF (l.lt.lmax(ig)) THEN
374                     entr(ig,l+1) = entr(ig,l+1) - ddd
375                     detr(ig,l) = 0.
376                     fm(ig,l+1) = fm(ig,l) + entr(ig,l)
377                  ELSE
378                     igout=ig
379                     lout=l
380                     labort_physic=.true.
381                  ENDIF
382               ENDIF
383            ENDIF
384         ENDDO
385         
386         IF (labort_physic) THEN
387            print *, ' ERROR: Entrainment is greater than its maximal authorized value!'
388            print *, '        Nor detrainment neither entrainment can compensate it!'
389            print *, 'ig,l,lmax', igout, lout, lmax(igout)
390            print *, 'entr  :', eee0
391            print *, 'detr  :', ddd0
392            print *, 'e_max :', masse(igout,lout)*fomass_max/ptimestep
393            print *, ' --- fomass_max :', fomass_max
394            print *, ' --- masse      :', masse(igout,lout)
395            print *, ' --- ptimestep  :', ptimestep
396            print *, 'eee :', eee
397            print *, 'ddd :', ddd
398            print *, 'fm-', fm(ig,l)
399            print *, 'entr,detr', entr(ig,l), detr(ig,l)
400            print *, 'fm+', fm(ig,l+1)
401            abort_message = 'problem in thermcell_flux'
402            CALL abort_physic (modname,abort_message,1)
403         ENDIF
404         
405!------------------------------------------------------------------------------
406! Test fraction couverte inferieure a alphamax
407!------------------------------------------------------------------------------
408         
409!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
410! FH : Partie a revisiter.
411!      Il semble qu'etaient codees ici deux optiques dans le cas F/(rho*w) > 1
412!      - soit limiter la hauteur du thermique en considerant que c'est
413!        la derniere chouche
414!      - soit limiter F a rho w.
415!      Dans le second cas, il faut en fait limiter a un peu moins que ca parce
416!      qu'on a des 1/(1-alpha) un peu plus loin dans thermcell_main et qu'il
417!      semble de toutes facons deraisonable d'avoir des fractions de 1...
418!      Ci-dessous, et dans l'etat actuel, le premier des deux if est sans doute inutile. 
419!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~                 
420         
421         DO ig=1,ngrid
422            zfm = rhobarz(ig,l+1) * zw2(ig,l+1) * alphamax
423            IF (fm(ig,l+1) .gt. zfm) THEN
424               f_old = fm(ig,l+1)
425               fm(ig,l+1) = zfm
426               detr(ig,l) = detr(ig,l) + f_old - fm(ig,l+1)
427               
428!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
429! AB : The previous change doesn't observe the equation df/dz = e - d.
430!      To avoid this issue, what is better to do? I choose to increase the
431!      entrainment in the layer above.
432!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
433               entr(ig,l+1) = entr(ig,l+1) + f_old - fm(ig,l+1)
434               
435               IF (prt_level.ge.10) THEN
436                  print *, 'Mass flux is modified in thermcell_flux'
437                  print *, 'ig,l,lmax', ig, l, lmax(ig)
438               ENDIF
439                 
440               IF (prt_level.ge.100) THEN
441                  print *, 'fm-', fm(ig,l)
442                  print *, 'entr,detr', entr(ig,l), detr(ig,l)
443                  print *, 'fm+', fm(ig,l+1)
444               ENDIF
445               
446               ncorecalpha = ncorecalpha+1
447               
448            ENDIF
449         ENDDO
450         
451!------------------------------------------------------------------------------
452! Test sur fm sortant positif
453!------------------------------------------------------------------------------
454         
455!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
456! AB : Is it usefull to do that?
457!      We will check fm in the first test with the next value of l
458!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
459!         DO ig=1,ngrid
460!            IF (fm(ig,l+1).lt.0.) THEN
461!               detr(ig,l) = detr(ig,l) + fm(ig,l+1)
462!               fm(ig,l+1) = 0.
463!               ncorecfm2  = ncorecfm2 + 1
464!            ENDIF
465!         ENDDO
466!         
467!         labort_physic=.false.
468!         
469!         DO ig=1,ngrid
470!            IF (detr(ig,l).lt.0.) THEN
471!               labort_physic = .true.
472!               igout = ig
473!               lout = l
474!            ENDIF
475!         ENDDO
476!         
477!         IF (labort_physic) THEN
478!            print *, ' ERROR: mass flux has negative value(s) and detrainement'
479!            print *, '        cannot compensate it!'
480!            print*,'ig,l,entr', igout, lout, entr(igout,lout)
481!            abort_message = 'negative outgoing fm in thermcell flux'
482!            CALL abort_physic (modname,abort_message,1)
483!         ENDIF
484         
485      ENDDO
486     
487!------------------------------------------------------------------------------
488! We check if fm, entr and detr vanish correctly in layer lmax
489!------------------------------------------------------------------------------
490     
491!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
492! AB : test added to avoid problem when lmax = 0, which is not a fortran index.
493!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
494      IF (lmax(ig).gt.0) THEN
495         DO ig=1,ngrid
496            detr(ig,lmax(ig)) = fm(ig,lmax(ig)) + entr(ig,lmax(ig))
497            fm(ig,lmax(ig)+1) = 0.
498            entr(ig,lmax(ig)) = 0.
499         ENDDO
500      ENDIF
501     
502!------------------------------------------------------------------------------
503! Impression des bidouilles utilisees pour corriger les problemes
504!------------------------------------------------------------------------------
505     
506      IF (prt_level.ge.1) THEN
507         
508! AB : those outputs are commented for their uselessness.
509!         IF (ncorecfm2.ge.1) THEN
510!            print *, 'WARNING: Outgoing mass flux has negative value(s)!'
511!            print *, 'in', ncorecfm2, 'point(s)'
512!         ENDIF
513         
514         IF (ncorecfm4.ge.1) THEN
515            print *, 'WARNING: Deacreasing updraft fraction above lalim!'
516            print *, 'in', ncorecfm4, 'point(s)'
517         ENDIF
518         
519         IF (ncorecfm5.ge.1) THEN
520            print *, 'WARNING: Increasing mass flux above lalim!'
521            print *, 'in', ncorecfm5, 'point(s)'
522         ENDIF
523         
524         IF (ncorecfm6.ge.1) THEN
525            print *, 'WARNING: Detrainment is greater than mass flux!'
526            print *, 'in', ncorecfm6, 'point(s)'
527         ENDIF
528         
529! AB : those outputs are commented because corresponding test is also commented.
530!         IF (ncorecfm7.ge.1) THEN
531!            print *, 'WARNING: Detrainment is greater than mass flux!'
532!            print *, 'in', ncorecfm7, 'point(s)'
533!         ENDIF
534         
535         IF (ncorecfm3.ge.1) THEN
536            print *, 'WARNING: Entrained mass is greater than its maximal authorized value!'
537            print *, 'in', ncorecfm3, 'point(s)'
538         ENDIF
539         
540         IF (ncorecalpha.ge.1) THEN
541            print *, 'WARNING: Updraft fraction is greater than its maximal authorized value!'
542            print *, 'in', ncorecalpha, 'point(s)'
543         ENDIF
544         
545      ENDIF
546     
547!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
548! AB : temporary test added to check the validity of eq. df/dz = e - d
549!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
550!      DO l=1,nlay
551!         DO ig=1,ngrid
552!            test = abs(fm(ig,l) + entr(ig,l) - detr(ig,l) - fm(ig,l+1))
553!            IF (test.gt.1.e-10) THEN
554!               print *, 'WARNING: df/dz != entr - detr'
555!               print *, 'ig,l', ig, l
556!               print *, 'fm-  :', fm(ig,l)
557!               print *, 'entr,detr', entr(ig,l), detr(ig,l)
558!               print *, 'fm+  :', fm(ig,l+1)
559!               print *, 'err. :', test
560!            ENDIF
561!         ENDDO
562!      ENDDO
563     
564     
565RETURN
566END
Note: See TracBrowser for help on using the repository browser.