source: lmdz_wrf/branches/LMDZ_WRFmeas/WRFV3/lmdz/thermcell_flux2.F90 @ 109

Last change on this file since 109 was 109, checked in by lfita, 10 years ago

Checking NaNs? from alim_star

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