source: LMDZ4/trunk/libf/phytherm/thermcell_flux.F90 @ 1072

Last change on this file since 1072 was 856, checked in by Laurent Fairhead, 17 years ago

Correction un peu trop rapide
LF

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