Changeset 855 for LMDZ4


Ignore:
Timestamp:
Oct 23, 2007, 3:03:13 PM (17 years ago)
Author:
Laurent Fairhead
Message:

Bidouillage interne :-)
LF

Location:
LMDZ4/trunk/libf/phytherm
Files:
1 deleted
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/phytherm/thermcell_flux.F90

    r852 r855  
     1!
     2! $Header$
     3!
     4
     5
    16      SUBROUTINE thermcell_flux(ngrid,klev,ptimestep,masse, &
    27     &       lalim,lmax,alim_star,  &
     
    152157    &    ptimestep,masse,entr,detr,fm,'2  ')
    153158
     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
    154184!-------------------------------------------------------------------------
    155185! Verification de la positivite des flux de masse
    156186!-------------------------------------------------------------------------
    157187
    158       do l=1,klev
     188!     do l=1,klev
    159189         do ig=1,ngrid
    160190            if (fm(ig,l+1).lt.0.) then
     
    165195            endif
    166196         enddo
    167       enddo
    168 
    169       if (lev_out.ge.10) &
    170     &    call printflux(ngrid,klev,lunout,igout,f,lmax,lalim, &
    171     &    ptimestep,masse,entr,detr,fm,'3  ')
     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)
    172202
    173203!-------------------------------------------------------------------------
     
    175205!-------------------------------------------------------------------------
    176206
    177       do l=1,klev
     207
     208      if (1.eq.0) then
     209!     do l=1,klev
    178210         do ig=1,ngrid
    179211          if (l.ge.lalim(ig).and.l.le.lmax(ig) &
     
    189221          endif
    190222        enddo
    191       enddo
    192 
    193       if (lev_out.ge.10) &
    194     &    call printflux(ngrid,klev,lunout,igout,f,lmax,lalim, &
    195     &    ptimestep,masse,entr,detr,fm,'4  ')
     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
    196231
    197232
     
    200235!-------------------------------------------------------------------------
    201236
    202       do l=1,klev
     237!     do l=1,klev
    203238         do ig=1,ngrid
    204239            if ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
     
    209244            endif
    210245         enddo
    211       enddo
    212 
    213       if (lev_out.ge.10) &
    214     &    call printflux(ngrid,klev,lunout,igout,f,lmax,lalim, &
    215     &    ptimestep,masse,entr,detr,fm,'5  ')
     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)
    216251
    217252!-------------------------------------------------------------------------
     
    221256      if(1.eq.1) then
    222257
    223       do l=1,klev
     258!     do l=1,klev
    224259         do ig=1,ngrid
    225260            if (entr(ig,l)<0.) then
     
    256291            endif
    257292         enddo
    258       enddo
    259       endif
    260 
    261 
    262       if (lev_out.ge.10) &
    263     &    call printflux(ngrid,klev,lunout,igout,f,lmax,lalim, &
    264     &    ptimestep,masse,entr,detr,fm,'6  ')
     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)
    265300
    266301!-------------------------------------------------------------------------
     
    268303!-------------------------------------------------------------------------
    269304
    270       do l=1,klev
     305!     do l=1,klev
    271306         do ig=1,ngrid
    272307            if (fm(ig,l+1).lt.0.) then
     
    283318            endif
    284319        enddo
    285      enddo
    286 
    287       if (lev_out.ge.10) &
    288     &    call printflux(ngrid,klev,lunout,igout,f,lmax,lalim, &
    289     &    ptimestep,masse,entr,detr,fm,'7  ')
     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)
    290325
    291326!-----------------------------------------------------------------------
     
    308343!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    309344
    310      if(1.eq.0) then
    311 
    312      do l=1,klev
     345!    do l=1,klev
    313346        do ig=1,ngrid
    314347           if (zw2(ig,l+1).gt.1.e-10) then
     
    327360           endif
    328361        enddo
    329      enddo
     362!    enddo
    330363!
     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
    331373      if (lev_out.ge.10) &
    332374    &    call printflux(ngrid,klev,lunout,igout,f,lmax,lalim, &
    333375    &    ptimestep,masse,entr,detr,fm,'8  ')
    334376
    335      endif
    336377
    337378!-----------------------------------------------------------------------
     
    418459      return
    419460      end
    420 
    421       subroutine printflux(ngrid,klev,lunout,igout,f,lmax,lalim, &
    422     &    ptimestep,masse,entr,detr,fm,descr)
    423 
    424      implicit none
    425 
    426       integer ngrid,klev,lunout,igout,l,lm
    427 
    428       integer lmax(klev),lalim(klev)
    429       real ptimestep,masse(ngrid,klev),entr(ngrid,klev),detr(ngrid,klev)
    430       real fm(ngrid,klev+1),f(ngrid)
    431 
    432       character*3 descr
    433 
    434       lm=lmax(igout)+5
    435       if(lm.gt.klev) lm=klev
    436 
    437       print*,'Impression jusque lm=',lm
    438 
    439          write(lunout,*) 'Dans thermcell_flux '//descr
    440          write(lunout,*) 'flux base ',f(igout)
    441          write(lunout,*) 'lmax ',lmax(igout)
    442          write(lunout,*) 'lalim ',lalim(igout)
    443          write(lunout,*) 'ig= ',igout
    444          write(lunout,'(a3,4a14)') 'l','M','E','D','F'
    445          write(lunout,'(i4,4e14.4)') (l,masse(igout,l)/ptimestep, &
    446      &     entr(igout,l),detr(igout,l) &
    447      &    ,fm(igout,l+1),l=1,lm)
    448 
    449 
    450       do l=lmax(igout)+1,klev
    451           if (abs(entr(igout,l))+abs(detr(igout,l))+abs(fm(igout,l)).gt.0.) then
    452           print*,'cas 1 : igout,l,lmax(igout)',igout,l,lmax(igout)
    453           print*,'entr(igout,l)',entr(igout,l)
    454           print*,'detr(igout,l)',detr(igout,l)
    455           print*,'fm(igout,l)',fm(igout,l)
    456           stop
    457           endif
    458       enddo
    459 
    460       return
    461       end
    462 
  • LMDZ4/trunk/libf/phytherm/thermcell_main.F90

    r852 r855  
    385385!-------------------------------------------------------------------------------
    386386
    387       CALL thermcell_flux2(ngrid,nlay,ptimestep,masse, &
     387      CALL thermcell_flux(ngrid,nlay,ptimestep,masse, &
    388388     &       lalim,lmax,alim_star,  &
    389389     &       entr_star,detr_star,f,rhobarz,zlev,zw2,fm,entr,  &
Note: See TracChangeset for help on using the changeset viewer.