Changeset 4133


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

Corrections thermiques pour replay

Location:
LMDZ6/trunk/libf/phylmd
Files:
3 edited

Legend:

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

    r2311 r4133  
    1717!=======================================================================
    1818
    19       integer ngrid,nlay,impl
    20 
    21       real ptimestep
    22       real masse(ngrid,nlay),fm(ngrid,nlay+1)
    23       real entr(ngrid,nlay)
    24       real q(ngrid,nlay)
    25       real dq(ngrid,nlay)
    26       integer lev_out                           ! niveau pour les print
    27 
    28       real qa(ngrid,nlay),detr(ngrid,nlay),wqd(ngrid,nlay+1)
    29 
     19! arguments
     20      integer, intent(in) :: ngrid,nlay,impl
     21      real, intent(in) :: ptimestep
     22      real, intent(in), dimension(ngrid,nlay) :: masse
     23      real, intent(inout), dimension(ngrid,nlay) :: entr,q
     24      real, intent(in), dimension(ngrid,nlay+1) :: fm
     25      real, intent(out), dimension(ngrid,nlay) :: dq,qa
     26      integer, intent(in) :: lev_out                           ! niveau pour les print
     27
     28! Local
     29      real, dimension(ngrid,nlay) :: detr,qold
     30      real, dimension(ngrid,nlay+1) :: wqd,fqa
    3031      real zzm
    31 
    3232      integer ig,k
    3333      real cfl
    3434
    35       real qold(ngrid,nlay),fqa(ngrid,nlay+1)
    3635      integer niter,iter
    3736      CHARACTER (LEN=20) :: modname='thermcell_dq'
     
    4342         call thermcell_dq_o(ngrid,nlay,impl,ptimestep,fm,entr,  &
    4443     &           masse,q,dq,qa,lev_out)
    45          return
     44         goto 1000
    4645      endif
    4746
     
    143142      enddo
    144143
    145 return
     1441000 continue
     145 RETURN
    146146end
    147147
  • 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
  • LMDZ6/trunk/libf/phylmd/thermcell_main.F90

    r4129 r4133  
    6161!    15 and 17 correspond to the activation of the stratocumulus "bidouille"
    6262!
     63! Using
     64!    abort_physic
     65!    iso_verif_aberrant_encadre
     66!    iso_verif_egalite
     67!    test_ltherm
     68!    thermcell_closure
     69!    thermcell_dq
     70!    thermcell_dry
     71!    thermcell_dv2
     72!    thermcell_env
     73!    thermcell_flux2
     74!    thermcell_height
     75!    thermcell_plume
     76!    thermcell_plume_5B
     77!    thermcell_plume_6A
     78!
    6379!=======================================================================
    6480
     
    7591      real, intent(in), dimension(ngrid,nlay)    :: pt,pu,pv,po,pplay,pphi,zpspsk
    7692      real, intent(in), dimension(ngrid,nlay+1)  :: pplev
     93      integer, intent(out), dimension(ngrid) :: lmax
    7794      real, intent(out), dimension(ngrid,nlay)   :: pdtadj,pduadj,pdvadj,pdoadj,entr0,detr0
    7895      real, intent(out), dimension(ngrid,nlay)   :: ztla,zqla,zqta,zqsatth,zthl
    7996      real, intent(out), dimension(ngrid,nlay+1) :: fm0,zw2,fraca
    80       real, intent(out), dimension(ngrid) :: zmax0,f0
     97      real, intent(inout), dimension(ngrid) :: zmax0,f0
    8198      real, intent(out), dimension(ngrid,nlay) :: ztva,ztv
    8299      logical, intent(in) :: debut
     100      real,intent(out), dimension(ngrid,nlay) :: ratqscth,ratqsdiff
    83101
    84102      real, intent(out), dimension(ngrid) :: pcon
     
    105123      logical sorties
    106124      real, dimension(ngrid) :: linter,zmix, zmax_sec
    107       integer,dimension(ngrid) :: lmax,lmin,lmix,lmix_bis,nivcon
     125      integer,dimension(ngrid) :: lmin,lmix,lmix_bis,nivcon
    108126      real, dimension(ngrid,nlay) :: ztva_est
    109127      real, dimension(ngrid,nlay) :: deltaz,zlay,zh,zdthladj,zu,zv,zo,zl,zva,zua,zoa
    110128      real, dimension(ngrid,nlay) :: zta,zha,q2,wq,wthl,wthv,thetath2,wth2
    111       real, dimension(ngrid,nlay) :: ratqscth,ratqsdiff,rho,masse
     129      real, dimension(ngrid,nlay) :: rho,masse
    112130      real, dimension(ngrid,nlay+1) :: zw_est,zlev
    113131      real, dimension(ngrid) :: wmax,wmax_tmp
     
    136154!   ---------------
    137155!
    138 
    139156   fm=0. ; entr=0. ; detr=0.
    140157
     
    706723      real seuil
    707724      character*21 comment
     725
    708726      seuil=0.25
    709727
Note: See TracChangeset for help on using the changeset viewer.