source: LMDZ6/trunk/libf/phylmd/thermcell_flux2.F90 @ 4127

Last change on this file since 4127 was 4089, checked in by fhourdin, 2 years ago

Reecriture des thermiques

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 16.4 KB
Line 
1!
2! $Id: thermcell_flux2.F90 4089 2022-03-10 18:23:47Z acozic $
3!
4      SUBROUTINE thermcell_flux2(ngrid,klev,ptimestep,masse, &
5     &       lalim,lmax,alim_star,  &
6     &       entr_star,detr_star,f,rhobarz,zlev,zw2,fm,entr,  &
7     &       detr,zqla,lev_out,lunout1,igout)
8!IM 060508    &       detr,zqla,zmax,lev_out,lunout,igout)
9
10
11!---------------------------------------------------------------------------
12!thermcell_flux: deduction des flux
13!---------------------------------------------------------------------------
14
15      USE thermcell_ini_mod, ONLY : prt_level,iflag_thermals_optflux
16      IMPLICIT NONE
17     
18      INTEGER ig,l
19      INTEGER ngrid,klev
20     
21      REAL alim_star(ngrid,klev),entr_star(ngrid,klev)
22      REAL detr_star(ngrid,klev)
23      REAL zw2(ngrid,klev+1)
24      REAL zlev(ngrid,klev+1)
25      REAL masse(ngrid,klev)
26      REAL ptimestep
27      REAL rhobarz(ngrid,klev)
28      REAL f(ngrid)
29      INTEGER lmax(ngrid)
30      INTEGER lalim(ngrid)
31      REAL zqla(ngrid,klev)
32      REAL zmax(ngrid)
33
34      integer ncorecfm1,ncorecfm2,ncorecfm3,ncorecalpha
35      integer ncorecfm4,ncorecfm5,ncorecfm6,ncorecfm7,ncorecfm8
36     
37
38      REAL entr(ngrid,klev),detr(ngrid,klev)
39      REAL fm(ngrid,klev+1)
40      REAL zfm
41
42      integer igout,lout
43      integer lev_out
44      integer lunout1
45
46      REAL f_old,ddd0,eee0,ddd,eee,zzz
47
48      REAL,SAVE :: fomass_max=0.5
49      REAL,SAVE :: alphamax=0.7
50!$OMP THREADPRIVATE(fomass_max,alphamax)
51
52      logical check_debug,labort_physic
53
54      character (len=20) :: modname='thermcell_flux2'
55      character (len=80) :: abort_message
56
57
58      ncorecfm1=0
59      ncorecfm2=0
60      ncorecfm3=0
61      ncorecfm4=0
62      ncorecfm5=0
63      ncorecfm6=0
64      ncorecfm7=0
65      ncorecfm8=0
66      ncorecalpha=0
67
68!initialisation
69      fm(:,:)=0.
70     
71      if (prt_level.ge.10) then
72         write(lunout1,*) 'Dans thermcell_flux 0'
73         write(lunout1,*) 'flux base ',f(igout)
74         write(lunout1,*) 'lmax ',lmax(igout)
75         write(lunout1,*) 'lalim ',lalim(igout)
76         write(lunout1,*) 'ig= ',igout
77         write(lunout1,*) ' l E*    A*     D*  '
78         write(lunout1,'(i4,3e15.5)') (l,entr_star(igout,l),alim_star(igout,l),detr_star(igout,l) &
79     &    ,l=1,lmax(igout))
80      endif
81
82
83!-------------------------------------------------------------------------
84! Verification de la nullite des entrainement et detrainement au dessus
85! de lmax(ig)
86! Active uniquement si check_debug=.true. ou prt_level>=10
87!-------------------------------------------------------------------------
88
89      check_debug=.false..or.prt_level>=10
90
91      if (check_debug) then
92      do l=1,klev
93         do ig=1,ngrid
94            if (l.le.lmax(ig)) then
95               if (entr_star(ig,l).gt.1.) then
96                    print*,'WARNING thermcell_flux 1 ig,l,lmax(ig)',ig,l,lmax(ig)
97                    print*,'entr_star(ig,l)',entr_star(ig,l)
98                    print*,'alim_star(ig,l)',alim_star(ig,l)
99                    print*,'detr_star(ig,l)',detr_star(ig,l)
100               endif
101            else
102               if (abs(entr_star(ig,l))+abs(alim_star(ig,l))+abs(detr_star(ig,l)).gt.0.) then
103                    print*,'cas 1 : ig,l,lmax(ig)',ig,l,lmax(ig)
104                    print*,'entr_star(ig,l)',entr_star(ig,l)
105                    print*,'alim_star(ig,l)',alim_star(ig,l)
106                    print*,'detr_star(ig,l)',detr_star(ig,l)
107                    abort_message = ''
108                    labort_physic=.true.
109                    CALL abort_physic (modname,abort_message,1)
110               endif
111            endif
112         enddo
113      enddo
114      endif
115
116!-------------------------------------------------------------------------
117! Multiplication par le flux de masse issu de la femreture
118!-------------------------------------------------------------------------
119
120      do l=1,klev
121         entr(:,l)=f(:)*(entr_star(:,l)+alim_star(:,l))
122         detr(:,l)=f(:)*detr_star(:,l)
123      enddo
124
125      if (prt_level.ge.10) then
126         write(lunout1,*) 'Dans thermcell_flux 1'
127         write(lunout1,*) 'flux base ',f(igout)
128         write(lunout1,*) 'lmax ',lmax(igout)
129         write(lunout1,*) 'lalim ',lalim(igout)
130         write(lunout1,*) 'ig= ',igout
131         write(lunout1,*) ' l   E    D     W2'
132         write(lunout1,'(i4,3e15.5)') (l,entr(igout,l),detr(igout,l) &
133     &    ,zw2(igout,l+1),l=1,lmax(igout))
134      endif
135
136      fm(:,1)=0.
137      do l=1,klev
138         do ig=1,ngrid
139            if (l.lt.lmax(ig)) then
140               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
141            elseif(l.eq.lmax(ig)) then
142               fm(ig,l+1)=0.
143               detr(ig,l)=fm(ig,l)+entr(ig,l)
144            else
145               fm(ig,l+1)=0.
146            endif
147         enddo
148      enddo
149
150
151
152! Test provisoire : pour comprendre pourquoi on corrige plein de fois
153! le cas fm6, on commence par regarder une premiere fois avant les
154! autres corrections.
155
156      do l=1,klev
157         do ig=1,ngrid
158            if (detr(ig,l).gt.fm(ig,l)) then
159               ncorecfm8=ncorecfm8+1
160!              igout=ig
161            endif
162         enddo
163      enddo
164
165!      if (prt_level.ge.10) &
166!    &    call printflux(ngrid,klev,lunout1,igout,f,lmax,lalim, &
167!    &    ptimestep,masse,entr,detr,fm,'2  ')
168
169
170
171!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
172! FH Version en cours de test;
173! par rapport a thermcell_flux, on fait une grande boucle sur "l"
174! et on modifie le flux avec tous les contr�les appliques d'affilee
175! pour la meme couche
176! Momentanement, on duplique le calcule du flux pour pouvoir comparer
177! les flux avant et apres modif
178!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
179
180      do l=1,klev
181
182         do ig=1,ngrid
183            if (l.lt.lmax(ig)) then
184               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
185            elseif(l.eq.lmax(ig)) then
186               fm(ig,l+1)=0.
187               detr(ig,l)=fm(ig,l)+entr(ig,l)
188            else
189               fm(ig,l+1)=0.
190            endif
191         enddo
192
193
194!-------------------------------------------------------------------------
195! Verification de la positivite des flux de masse
196!-------------------------------------------------------------------------
197
198!     do l=1,klev
199         do ig=1,ngrid
200            if (fm(ig,l+1).lt.0.) then
201!              print*,'fm1<0',l+1,lmax(ig),fm(ig,l+1)
202                ncorecfm1=ncorecfm1+1
203               fm(ig,l+1)=fm(ig,l)
204               detr(ig,l)=entr(ig,l)
205            endif
206         enddo
207!     enddo
208
209      if (prt_level.ge.10) &
210     &   write(lunout1,'(i4,4e14.4)') l,masse(igout,l)/ptimestep, &
211     &     entr(igout,l),detr(igout,l),fm(igout,l+1)
212
213!-------------------------------------------------------------------------
214!Test sur fraca croissant
215!-------------------------------------------------------------------------
216      if (iflag_thermals_optflux==0) then
217!     do l=1,klev
218         do ig=1,ngrid
219          if (l.ge.lalim(ig).and.l.le.lmax(ig) &
220     &    .and.(zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10) ) then
221!  zzz est le flux en l+1 a frac constant
222             zzz=fm(ig,l)*rhobarz(ig,l+1)*zw2(ig,l+1)  &
223     &                          /(rhobarz(ig,l)*zw2(ig,l))
224             if (fm(ig,l+1).gt.zzz) then
225                detr(ig,l)=detr(ig,l)+fm(ig,l+1)-zzz
226                fm(ig,l+1)=zzz
227                ncorecfm4=ncorecfm4+1
228             endif
229          endif
230        enddo
231!     enddo
232      endif
233
234      if (prt_level.ge.10) &
235     &   write(lunout1,'(i4,4e14.4)') l,masse(igout,l)/ptimestep, &
236     &     entr(igout,l),detr(igout,l),fm(igout,l+1)
237
238
239!-------------------------------------------------------------------------
240!test sur flux de masse croissant
241!-------------------------------------------------------------------------
242      if (iflag_thermals_optflux==0) then
243!     do l=1,klev
244         do ig=1,ngrid
245            if ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
246              f_old=fm(ig,l+1)
247              fm(ig,l+1)=fm(ig,l)
248              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
249               ncorecfm5=ncorecfm5+1
250            endif
251         enddo
252!     enddo
253      endif
254
255      if (prt_level.ge.10) &
256     &   write(lunout1,'(i4,4e14.4)') l,masse(igout,l)/ptimestep, &
257     &     entr(igout,l),detr(igout,l),fm(igout,l+1)
258
259!fin 1.eq.0
260!-------------------------------------------------------------------------
261!detr ne peut pas etre superieur a fm
262!-------------------------------------------------------------------------
263
264      if(1.eq.1) then
265
266!     do l=1,klev
267
268
269
270         labort_physic=.false.
271         do ig=1,ngrid
272            if (entr(ig,l)<0.) then
273               labort_physic=.true.
274               igout=ig
275               lout=l
276            endif
277         enddo
278
279         if (labort_physic) then
280            print*,'N1 ig,l,entr',igout,lout,entr(igout,lout)
281            abort_message = 'entr negatif'
282            CALL abort_physic (modname,abort_message,1)
283         endif
284
285         do ig=1,ngrid
286            if (detr(ig,l).gt.fm(ig,l)) then
287               ncorecfm6=ncorecfm6+1
288               detr(ig,l)=fm(ig,l)
289               entr(ig,l)=fm(ig,l+1)
290
291! Dans le cas ou on est au dessus de la couche d'alimentation et que le
292! detrainement est plus fort que le flux de masse, on stope le thermique.
293!test:on commente
294!               if (l.gt.lalim(ig)) then
295!                  lmax(ig)=l
296!                  fm(ig,l+1)=0.
297!                  entr(ig,l)=0.
298!               else
299!                  ncorecfm7=ncorecfm7+1
300!               endif
301            endif
302
303            if(l.gt.lmax(ig)) then
304               detr(ig,l)=0.
305               fm(ig,l+1)=0.
306               entr(ig,l)=0.
307            endif
308         enddo
309
310         labort_physic=.false.
311         do ig=1,ngrid
312            if (entr(ig,l).lt.0.) then
313               labort_physic=.true.
314               igout=ig
315            endif
316         enddo
317         if (labort_physic) then
318            ig=igout
319            print*,'ig,l,lmax(ig)',ig,l,lmax(ig)
320            print*,'entr(ig,l)',entr(ig,l)
321            print*,'fm(ig,l)',fm(ig,l)
322            abort_message = 'probleme dans thermcell flux'
323            CALL abort_physic (modname,abort_message,1)
324         endif
325
326
327!     enddo
328      endif
329
330
331      if (prt_level.ge.10) &
332     &   write(lunout1,'(i4,4e14.4)') l,masse(igout,l)/ptimestep, &
333     &     entr(igout,l),detr(igout,l),fm(igout,l+1)
334
335!-------------------------------------------------------------------------
336!fm ne peut pas etre negatif
337!-------------------------------------------------------------------------
338
339!     do l=1,klev
340         do ig=1,ngrid
341            if (fm(ig,l+1).lt.0.) then
342               detr(ig,l)=detr(ig,l)+fm(ig,l+1)
343               fm(ig,l+1)=0.
344               ncorecfm2=ncorecfm2+1
345            endif
346         enddo
347
348         labort_physic=.false.
349         do ig=1,ngrid
350            if (detr(ig,l).lt.0.) then
351               labort_physic=.true.
352               igout=ig
353            endif
354        enddo
355        if (labort_physic) then
356               ig=igout
357               print*,'cas 2 : ig,l,lmax(ig)',ig,l,lmax(ig)
358               print*,'detr(ig,l)',detr(ig,l)
359               print*,'fm(ig,l)',fm(ig,l)
360               abort_message = 'probleme dans thermcell flux'
361               CALL abort_physic (modname,abort_message,1)
362        endif
363!    enddo
364
365      if (prt_level.ge.10) &
366     &   write(lunout1,'(i4,4e14.4)') l,masse(igout,l)/ptimestep, &
367     &     entr(igout,l),detr(igout,l),fm(igout,l+1)
368
369!-----------------------------------------------------------------------
370!la fraction couverte ne peut pas etre superieure a 1           
371!-----------------------------------------------------------------------
372
373
374!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
375! FH Partie a revisiter.
376! Il semble qu'etaient codees ici deux optiques dans le cas
377! F/ (rho *w) > 1
378! soit limiter la hauteur du thermique en considerant que c'est
379! la derniere chouche, soit limiter F a rho w.
380! Dans le second cas, il faut en fait limiter a un peu moins
381! que ca parce qu'on a des 1 / ( 1 -alpha) un peu plus loin
382! dans thermcell_main et qu'il semble de toutes facons deraisonable
383! d'avoir des fractions de 1..
384! Ci dessous, et dans l'etat actuel, le premier des  deux if est
385! sans doute inutile.
386!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
387
388!    do l=1,klev
389        do ig=1,ngrid
390           if (zw2(ig,l+1).gt.1.e-10) then
391           zfm=rhobarz(ig,l+1)*zw2(ig,l+1)*alphamax
392           if ( fm(ig,l+1) .gt. zfm) then
393              f_old=fm(ig,l+1)
394              fm(ig,l+1)=zfm
395!             zw2(ig,l+1)=0.
396!             zqla(ig,l+1)=0.
397              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
398!             lmax(ig)=l+1
399!             zmax(ig)=zlev(ig,lmax(ig))
400!             print*,'alpha>1',l+1,lmax(ig)
401              ncorecalpha=ncorecalpha+1
402           endif
403           endif
404        enddo
405!    enddo
406!
407
408
409      if (prt_level.ge.10) &
410     &   write(lunout1,'(i4,4e14.4)') l,masse(igout,l)/ptimestep, &
411     &     entr(igout,l),detr(igout,l),fm(igout,l+1)
412
413! Fin de la grande boucle sur les niveaux verticaux
414      enddo
415
416!      if (prt_level.ge.10) &
417!    &    call printflux(ngrid,klev,lunout1,igout,f,lmax,lalim, &
418!    &    ptimestep,masse,entr,detr,fm,'8  ')
419
420
421!-----------------------------------------------------------------------
422! On fait en sorte que la quantite totale d'air entraine dans le
423! panache ne soit pas trop grande comparee a la masse de la maille
424!-----------------------------------------------------------------------
425
426      if (1.eq.1) then
427      labort_physic=.false.
428      do l=1,klev-1
429         do ig=1,ngrid
430            eee0=entr(ig,l)
431            ddd0=detr(ig,l)
432            eee=entr(ig,l)-masse(ig,l)*fomass_max/ptimestep
433            ddd=detr(ig,l)-eee
434            if (eee.gt.0.) then
435                ncorecfm3=ncorecfm3+1
436                entr(ig,l)=entr(ig,l)-eee
437                if ( ddd.gt.0.) then
438!   l'entrainement est trop fort mais l'exces peut etre compense par une
439!   diminution du detrainement)
440                   detr(ig,l)=ddd
441                else
442!   l'entrainement est trop fort mais l'exces doit etre compense en partie
443!   par un entrainement plus fort dans la couche superieure
444                   if(l.eq.lmax(ig)) then
445                      detr(ig,l)=fm(ig,l)+entr(ig,l)
446                   else
447                      if(l.ge.lmax(ig).and.0.eq.1) then
448                         igout=ig
449                         lout=l
450                         labort_physic=.true.
451                      endif
452                      entr(ig,l+1)=entr(ig,l+1)-ddd
453                      detr(ig,l)=0.
454                      fm(ig,l+1)=fm(ig,l)+entr(ig,l)
455                      detr(ig,l)=0.
456                   endif
457                endif
458            endif
459         enddo
460      enddo
461      if (labort_physic) then
462                         ig=igout
463                         l=lout
464                         print*,'ig,l',ig,l
465                         print*,'eee0',eee0
466                         print*,'ddd0',ddd0
467                         print*,'eee',eee
468                         print*,'ddd',ddd
469                         print*,'entr',entr(ig,l)
470                         print*,'detr',detr(ig,l)
471                         print*,'masse',masse(ig,l)
472                         print*,'fomass_max',fomass_max
473                         print*,'masse(ig,l)*fomass_max/ptimestep',masse(ig,l)*fomass_max/ptimestep
474                         print*,'ptimestep',ptimestep
475                         print*,'lmax(ig)',lmax(ig)
476                         print*,'fm(ig,l+1)',fm(ig,l+1)
477                         print*,'fm(ig,l)',fm(ig,l)
478                         abort_message = 'probleme dans thermcell_flux'
479                         CALL abort_physic (modname,abort_message,1)
480      endif
481      endif
482!                 
483!              ddd=detr(ig)-entre
484!on s assure que tout s annule bien en zmax
485      do ig=1,ngrid
486         fm(ig,lmax(ig)+1)=0.
487         entr(ig,lmax(ig))=0.
488         detr(ig,lmax(ig))=fm(ig,lmax(ig))+entr(ig,lmax(ig))
489      enddo
490
491!-----------------------------------------------------------------------
492! Impression du nombre de bidouilles qui ont ete necessaires
493!-----------------------------------------------------------------------
494
495!IM 090508 beg
496!     if (ncorecfm1+ncorecfm2+ncorecfm3+ncorecfm4+ncorecfm5+ncorecalpha > 0 ) then
497!
498!         print*,'PB thermcell : on a du coriger ',ncorecfm1,'x fm1',&
499!   &     ncorecfm2,'x fm2',ncorecfm3,'x fm3 et', &
500!   &     ncorecfm4,'x fm4',ncorecfm5,'x fm5 et', &
501!   &     ncorecfm6,'x fm6', &
502!   &     ncorecfm7,'x fm7', &
503!   &     ncorecfm8,'x fm8', &
504!   &     ncorecalpha,'x alpha'
505!     endif
506!IM 090508 end
507
508!      if (prt_level.ge.10) &
509!    &    call printflux(ngrid,klev,lunout1,igout,f,lmax,lalim, &
510!    &    ptimestep,masse,entr,detr,fm,'fin')
511
512
513      return
514      end
Note: See TracBrowser for help on using the repository browser.