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

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

Rajout de la physique utilisant les thermiques FH
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.3 KB
Line 
1      SUBROUTINE thermcell_flux(ngrid,klev,ptimestep,masse, &
2     &       lalim,lmax,alim_star,  &
3     &       entr_star,detr_star,f,rhobarz,zlev,zw2,fm,entr,  &
4     &       detr,zqla,zmax,lev_out,lunout,igout)
5
6
7!---------------------------------------------------------------------------
8!thermcell_flux: deduction des flux
9!---------------------------------------------------------------------------
10
11      IMPLICIT NONE
12     
13      INTEGER ig,l
14      INTEGER ngrid,klev
15     
16      REAL alim_star(ngrid,klev),entr_star(ngrid,klev)
17      REAL detr_star(ngrid,klev)
18      REAL zw2(ngrid,klev+1)
19      REAL zlev(ngrid,klev+1)
20      REAL masse(ngrid,klev)
21      REAL ptimestep
22      REAL rhobarz(ngrid,klev)
23      REAL f(ngrid)
24      INTEGER lmax(ngrid)
25      INTEGER lalim(ngrid)
26      REAL zqla(ngrid,klev)
27      REAL zmax(ngrid)
28
29      integer ncorecfm1,ncorecfm2,ncorecfm3,ncorecalpha
30      integer ncorecfm4,ncorecfm5,ncorecfm6
31     
32
33      REAL entr(ngrid,klev),detr(ngrid,klev)
34      REAL fm(ngrid,klev+1)
35
36      integer igout
37      integer lev_out
38      integer lunout
39
40      REAL f_old,ddd0,eee0,ddd,eee,zzz
41
42      REAL fracmax
43      save fracmax
44
45      fracmax=0.5
46
47      ncorecfm1=0
48      ncorecfm2=0
49      ncorecfm3=0
50      ncorecfm4=0
51      ncorecfm5=0
52      ncorecfm6=0
53      ncorecalpha=0
54
55!initialisation
56      fm(:,:)=0.
57     
58
59!-------------------------------------------------------------------------
60! Verification de la nullite des entrainement et detrainement au dessus
61! de lmax(ig)
62!-------------------------------------------------------------------------
63
64      do l=1,klev
65         do ig=1,ngrid
66            if (l.le.lmax(ig)) then
67               if (entr_star(ig,l).gt.1.) then
68                    print*,'ig,l,lmax(ig)',ig,l,lmax(ig)
69                    print*,'entr_star(ig,l)',entr_star(ig,l)
70                    print*,'alim_star(ig,l)',alim_star(ig,l)
71                    print*,'detr_star(ig,l)',detr_star(ig,l)
72                    stop
73               endif
74            else
75               if (abs(entr_star(ig,l))+abs(alim_star(ig,l))+abs(detr_star(ig,l)).gt.0) then
76                    print*,'ig,l,lmax(ig)',ig,l,lmax(ig)
77                    print*,'entr_star(ig,l)',entr_star(ig,l)
78                    print*,'alim_star(ig,l)',alim_star(ig,l)
79                    print*,'detr_star(ig,l)',detr_star(ig,l)
80                    stop
81               endif
82            endif
83         enddo
84      enddo
85
86!-------------------------------------------------------------------------
87! Multiplication par le flux de masse issu de la femreture
88!-------------------------------------------------------------------------
89
90      do l=1,klev
91         entr(:,l)=f(:)*(entr_star(:,l)+alim_star(:,l))
92         detr(:,l)=f(:)*detr_star(:,l)
93      enddo
94
95      fm(:,1)=0.
96      do l=1,klev
97         do ig=1,ngrid
98            if (l.lt.lmax(ig)) then
99               fm(ig,l+1)=fm(ig,l)+entr(ig,l)-detr(ig,l)
100            elseif(l.eq.lmax(ig)) then
101               fm(ig,l+1)=0.
102               detr(ig,l)=fm(ig,l)+entr(ig,l)
103            else
104               fm(ig,l+1)=0.
105            endif
106         enddo
107      enddo
108
109      if (lev_out.ge.10) then
110         write(lunout,*) 'Dans thermcell_flux 1'
111         write(lunout,*) 'flux base ',f(igout)
112         write(lunout,*) 'lmax ',lmax(igout)
113         write(lunout,*) 'lalim ',lalim(igout)
114         write(lunout,'(i6,i4,3e15.5)') (ig,l,entr(igout,l),detr(igout,l) &
115     &    ,fm(igout,l+1),l=1,lmax(igout))
116      endif
117
118!-------------------------------------------------------------------------
119! Verification de la positivite des flux de masse
120!-------------------------------------------------------------------------
121
122      do l=1,klev
123         do ig=1,ngrid
124            if (fm(ig,l+1).lt.0.) then
125!              print*,'fm1<0',l+1,lmax(ig),fm(ig,l+1)
126                ncorecfm1=ncorecfm1+1
127               fm(ig,l+1)=fm(ig,l)
128               detr(ig,l)=entr(ig,l)
129            endif
130         enddo
131      enddo
132
133!-------------------------------------------------------------------------
134!Test sur fraca croissant
135!-------------------------------------------------------------------------
136
137      do l=1,klev
138         do ig=1,ngrid
139          if (l.ge.lalim(ig).and.l.le.lmax(ig) &
140     &    .and.(zw2(ig,l+1).gt.1.e-10).and.(zw2(ig,l).gt.1.e-10) ) then
141!  zzz est le flux en l+1 a frac constant
142             zzz=fm(ig,l)*rhobarz(ig,l+1)*zw2(ig,l+1)  &
143     &                          /(rhobarz(ig,l)*zw2(ig,l))
144             if (fm(ig,l+1).gt.zzz) then
145                detr(ig,l)=detr(ig,l)+fm(ig,l+1)-zzz
146                fm(ig,l+1)=zzz
147                ncorecfm4=ncorecfm4+1
148             endif
149          endif
150        enddo
151      enddo
152
153
154!-------------------------------------------------------------------------
155!test sur flux de masse croissant
156!-------------------------------------------------------------------------
157
158      do l=1,klev
159         do ig=1,ngrid
160            if ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
161              f_old=fm(ig,l+1)
162              fm(ig,l+1)=fm(ig,l)
163              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
164               ncorecfm5=ncorecfm5+1
165            endif
166         enddo
167      enddo
168
169!-------------------------------------------------------------------------
170!detr ne peut pas etre superieur a fm
171!-------------------------------------------------------------------------
172
173      if(1.eq.1) then
174      do l=1,klev
175         do ig=1,ngrid
176            if (entr(ig,l)<0.) then
177               print*,'N1 ig,l,entr',ig,l,entr(ig,l)
178               stop'entr negatif'
179            endif
180            if (detr(ig,l).gt.fm(ig,l)) then
181               ncorecfm6=ncorecfm6+1
182               detr(ig,l)=fm(ig,l)
183               entr(ig,l)=fm(ig,l+1)
184            endif
185            if (entr(ig,l).lt.0.) then
186               print*,'ig,l,lmax(ig)',ig,l,lmax(ig)
187               print*,'entr(ig,l)',entr(ig,l)
188               print*,'fm(ig,l)',fm(ig,l)
189               stop'probleme dans thermcell flux'
190            endif
191         enddo
192      enddo
193      endif
194
195
196!-------------------------------------------------------------------------
197!fm ne peut pas etre negatif
198!-------------------------------------------------------------------------
199
200      do l=1,klev
201         do ig=1,ngrid
202            if (fm(ig,l+1).lt.0.) then
203               detr(ig,l)=detr(ig,l)+fm(ig,l+1)
204               fm(ig,l+1)=0.
205!              print*,'fm2<0',l+1,lmax(ig)
206               ncorecfm2=ncorecfm2+1
207            endif
208            if (detr(ig,l).lt.0.) then
209               print*,'ig,l,lmax(ig)',ig,l,lmax(ig)
210               print*,'detr(ig,l)',detr(ig,l)
211               print*,'fm(ig,l)',fm(ig,l)
212               stop'probleme dans thermcell flux'
213            endif
214        enddo
215     enddo
216
217!-----------------------------------------------------------------------
218!la fraction couverte ne peut pas etre superieure a 1           
219!-----------------------------------------------------------------------
220     do l=1,klev
221        do ig=1,ngrid
222           if (zw2(ig,l+1).gt.1.e-10) then
223           if ((((fm(ig,l+1))/(rhobarz(ig,l+1)*zw2(ig,l+1))).gt.  &
224     &      1.)) then
225              f_old=fm(ig,l+1)
226              fm(ig,l+1)=rhobarz(ig,l+1)*zw2(ig,l+1)
227              zw2(ig,l+1)=0.
228              zqla(ig,l+1)=0.
229              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
230              lmax(ig)=l+1
231              zmax(ig)=zlev(ig,lmax(ig))
232!             print*,'alpha>1',l+1,lmax(ig)
233              ncorecalpha=ncorecalpha+1
234           endif
235           endif
236        enddo
237     enddo
238!
239
240!-----------------------------------------------------------------------
241! On fait en sorte que la quantite totale d'air entraine dans le
242! panache ne soit pas trop grande comparee a la masse de la maille
243!-----------------------------------------------------------------------
244
245      if (1.eq.1) then
246      do l=1,klev-1
247         do ig=1,ngrid
248            eee0=entr(ig,l)
249            ddd0=detr(ig,l)
250            eee=entr(ig,l)-masse(ig,l)*fracmax/ptimestep
251            ddd=detr(ig,l)-eee
252            if (eee.gt.0.) then
253                ncorecfm3=ncorecfm3+1
254                entr(ig,l)=entr(ig,l)-eee
255                if ( ddd.gt.0.) then
256!   l'entrainement est trop fort mais l'exces peut etre compense par une
257!   diminution du detrainement)
258                   detr(ig,l)=ddd
259                else
260!   l'entrainement est trop fort mais l'exces doit etre compense en partie
261!   par un entrainement plus fort dans la couche superieure
262                   if(l.eq.lmax(ig)) then
263                      detr(ig,l)=fm(ig,l)+entr(ig,l)
264                   else
265                      if(l.ge.lmax(ig).and.0.eq.1) then
266                         print*,'ig,l',ig,l
267                         print*,'eee0',eee0
268                         print*,'ddd0',ddd0
269                         print*,'eee',eee
270                         print*,'ddd',ddd
271                         print*,'entr',entr(ig,l)
272                         print*,'detr',detr(ig,l)
273                         print*,'masse',masse(ig,l)
274                         print*,'fracmax',fracmax
275                         print*,'masse(ig,l)*fracmax/ptimestep',masse(ig,l)*fracmax/ptimestep
276                         print*,'ptimestep',ptimestep
277                         print*,'lmax(ig)',lmax(ig)
278                         print*,'fm(ig,l+1)',fm(ig,l+1)
279                         print*,'fm(ig,l)',fm(ig,l)
280                         stop'probleme dans thermcell_flux'
281                      endif
282                      entr(ig,l+1)=entr(ig,l+1)-ddd
283                      detr(ig,l)=0.
284                      fm(ig,l+1)=fm(ig,l)+entr(ig,l)
285                      detr(ig,l)=0.
286                   endif
287                endif
288            endif
289         enddo
290      enddo
291      endif
292!                 
293!              ddd=detr(ig)-entre
294!on s assure que tout s annule bien en zmax
295      do ig=1,ngrid
296         fm(ig,lmax(ig)+1)=0.
297         entr(ig,lmax(ig))=0.
298         detr(ig,lmax(ig))=fm(ig,lmax(ig))+entr(ig,lmax(ig))
299      enddo
300
301!-----------------------------------------------------------------------
302! Impression du nombre de bidouilles qui ont ete necessaires
303!-----------------------------------------------------------------------
304
305      if (ncorecfm1+ncorecfm2+ncorecfm3+ncorecfm4+ncorecfm5+ncorecalpha > 0 ) then
306
307          print*,'PB thermcell : on a du coriger ',ncorecfm1,'x fm1',&
308    &     ncorecfm2,'x fm2',ncorecfm3,'x fm3 et', &
309    &     ncorecfm4,'x fm4',ncorecfm5,'x fm5 et', &
310    &     ncorecfm6,'x fm6', &
311    &     ncorecalpha,'x alpha'
312      endif
313
314
315      return
316      end
Note: See TracBrowser for help on using the repository browser.