Ignore:
Timestamp:
Apr 20, 2022, 11:44:24 PM (2 years ago)
Author:
fhourdin
Message:

Corrections thermiques pour replay

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/thermcell_flux2.F90

    r4089 r4133  
    22! $Id$
    33!
    4       SUBROUTINE thermcell_flux2(ngrid,klev,ptimestep,masse, &
     4      SUBROUTINE thermcell_flux2(ngrid,nlay,ptimestep,masse, &
    55     &       lalim,lmax,alim_star,  &
    66     &       entr_star,detr_star,f,rhobarz,zlev,zw2,fm,entr,  &
     
    1616      IMPLICIT NONE
    1717     
     18! arguments
     19      INTEGER, intent(in) :: ngrid,nlay
     20      REAL, intent(in) :: ptimestep
     21      REAL, intent(in), dimension(ngrid,nlay) :: masse
     22      INTEGER, intent(in), dimension(ngrid) :: lalim,lmax
     23      REAL, intent(in), dimension(ngrid,nlay) :: alim_star,entr_star,detr_star
     24      REAL, intent(in), dimension(ngrid) :: f
     25      REAL, intent(in), dimension(ngrid,nlay) :: rhobarz
     26      REAL, intent(in), dimension(ngrid,nlay+1) :: zw2,zlev
     27! FH : laisser ca le temps de verifier qu'on a bien fait de commenter les
     28!      lignes faisant apparaitre zqla, zmax ...
     29!     REAL, intent(in), dimension(ngrid) :: zmax(ngrid)
     30!     enlever aussi zqla
     31      REAL, intent(in), dimension(ngrid,nlay) :: zqla  ! not used
     32      integer, intent(in) :: lev_out, lunout1
     33
     34      REAL,intent(out), dimension(ngrid,nlay) :: entr,detr
     35      REAL,intent(out), dimension(ngrid,nlay+1) :: fm
     36
     37! local
    1838      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 
     39      integer igout,lout
     40      REAL zfm
    3441      integer ncorecfm1,ncorecfm2,ncorecfm3,ncorecalpha
    3542      integer ncorecfm4,ncorecfm5,ncorecfm6,ncorecfm7,ncorecfm8
    3643     
    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
    4544
    4645      REAL f_old,ddd0,eee0,ddd,eee,zzz
     
    9089
    9190      if (check_debug) then
    92       do l=1,klev
     91      do l=1,nlay
    9392         do ig=1,ngrid
    9493            if (l.le.lmax(ig)) then
     
    118117!-------------------------------------------------------------------------
    119118
    120       do l=1,klev
     119      do l=1,nlay
    121120         entr(:,l)=f(:)*(entr_star(:,l)+alim_star(:,l))
    122121         detr(:,l)=f(:)*detr_star(:,l)
     
    135134
    136135      fm(:,1)=0.
    137       do l=1,klev
     136      do l=1,nlay
    138137         do ig=1,ngrid
    139138            if (l.lt.lmax(ig)) then
     
    154153! autres corrections.
    155154
    156       do l=1,klev
     155      do l=1,nlay
    157156         do ig=1,ngrid
    158157            if (detr(ig,l).gt.fm(ig,l)) then
     
    164163
    165164!      if (prt_level.ge.10) &
    166 !    &    call printflux(ngrid,klev,lunout1,igout,f,lmax,lalim, &
     165!    &    call printflux(ngrid,nlay,lunout1,igout,f,lmax,lalim, &
    167166!    &    ptimestep,masse,entr,detr,fm,'2  ')
    168167
     
    178177!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    179178
    180       do l=1,klev
     179      do l=1,nlay
    181180
    182181         do ig=1,ngrid
     
    196195!-------------------------------------------------------------------------
    197196
    198 !     do l=1,klev
     197!     do l=1,nlay
    199198         do ig=1,ngrid
    200199            if (fm(ig,l+1).lt.0.) then
     
    215214!-------------------------------------------------------------------------
    216215      if (iflag_thermals_optflux==0) then
    217 !     do l=1,klev
     216!     do l=1,nlay
    218217         do ig=1,ngrid
    219218          if (l.ge.lalim(ig).and.l.le.lmax(ig) &
     
    241240!-------------------------------------------------------------------------
    242241      if (iflag_thermals_optflux==0) then
    243 !     do l=1,klev
     242!     do l=1,nlay
    244243         do ig=1,ngrid
    245244            if ((fm(ig,l+1).gt.fm(ig,l)).and.(l.gt.lalim(ig))) then
     
    264263      if(1.eq.1) then
    265264
    266 !     do l=1,klev
     265!     do l=1,nlay
    267266
    268267
     
    337336!-------------------------------------------------------------------------
    338337
    339 !     do l=1,klev
     338!     do l=1,nlay
    340339         do ig=1,ngrid
    341340            if (fm(ig,l+1).lt.0.) then
     
    386385!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    387386
    388 !    do l=1,klev
     387!    do l=1,nlay
    389388        do ig=1,ngrid
    390389           if (zw2(ig,l+1).gt.1.e-10) then
     
    393392              f_old=fm(ig,l+1)
    394393              fm(ig,l+1)=zfm
    395 !             zw2(ig,l+1)=0.
    396 !             zqla(ig,l+1)=0.
    397394              detr(ig,l)=detr(ig,l)+f_old-fm(ig,l+1)
    398395!             lmax(ig)=l+1
     
    415412
    416413!      if (prt_level.ge.10) &
    417 !    &    call printflux(ngrid,klev,lunout1,igout,f,lmax,lalim, &
     414!    &    call printflux(ngrid,nlay,lunout1,igout,f,lmax,lalim, &
    418415!    &    ptimestep,masse,entr,detr,fm,'8  ')
    419416
     
    426423      if (1.eq.1) then
    427424      labort_physic=.false.
    428       do l=1,klev-1
     425      do l=1,nlay-1
    429426         do ig=1,ngrid
    430427            eee0=entr(ig,l)
     
    507504
    508505!      if (prt_level.ge.10) &
    509 !    &    call printflux(ngrid,klev,lunout1,igout,f,lmax,lalim, &
     506!    &    call printflux(ngrid,nlay,lunout1,igout,f,lmax,lalim, &
    510507!    &    ptimestep,masse,entr,detr,fm,'fin')
    511508
    512509
    513       return
     510 RETURN
    514511      end
Note: See TracChangeset for help on using the changeset viewer.