Changeset 2229


Ignore:
Timestamp:
Jan 29, 2020, 6:28:42 PM (5 years ago)
Author:
aboissinot
Message:

A bug in thermcell_dq is fixed. Now zqt is correctly initialized when tracer h2o_vap
is missing (consistency with flag water is assumed).

Useless arguments in thermcell_dq subroutine are removed (lmin, lmax)

Location:
trunk/LMDZ.GENERIC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/README

    r2178 r2229  
    14691469- some fixes for the slab ocean. Still need to make it work in parallel.
    14701470
    1471 == 26/02/2019 == AB
     1471== 26/03/2019 == AB
    14721472- new formulae to compute vertical speed in thermcell_plume
    14731473- fix an inconsistency in zdttherm and zdqtherm computation according to water key value in physiq_mod
     
    14991499- Cleanup thermal plums model subroutines (thermcell_main, thermcell_env, thercell_dq, thermcell_dv2, thermcell_closure, thermcell_height)
    15001500- In thermcell_plume, restore initial formula to compute the vertical speed and cleanup the file
     1501
     1502== 29/01/2019 == AB
     1503- fix a bug in thermcell_dq. Now zqt is correctly initialized when tracer h2o_vap is missing (consistency with flag water is assumed).
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_dq.F90

    r2177 r2229  
    33!
    44SUBROUTINE thermcell_dq(ngrid,nlay,ptimestep,fm,entr,detr,masse,              &
    5                         q,dq,qa,lmin,lmax)
     5                        q,dq,qa)
    66     
    77     
     
    2222     
    2323      USE print_control_mod, ONLY: prt_level
    24       USe thermcell_mod, ONLY: dqimpl
     24      USE thermcell_mod, ONLY: dqimpl
    2525     
    2626      IMPLICIT NONE
     
    3636      INTEGER, INTENT(in) :: ngrid
    3737      INTEGER, INTENT(in) :: nlay
    38       INTEGER, INTENT(in) :: lmin(ngrid)
    39       INTEGER, INTENT(in) :: lmax(ngrid)
    4038     
    4139      REAL, INTENT(in) :: ptimestep
     
    8785               print *, 'ERROR: entrainment is greater than the layer mass!'
    8886               print *, 'ig,l,entr', ig, l, entr(ig,l)
    89                print *, 'lmin,lmax', lmin(ig), lmax(ig)
    9087               print *, '-------------------------------'
    9188               print *, 'entr*dt,mass', entr(ig,l)*ptimestep, masse(ig,l)
     
    107104     
    108105      DO ig=1,ngrid
    109          DO l=1,lmin(ig)
    110             qa(ig,l) = q(ig,l)
    111          ENDDO
    112       ENDDO
    113      
    114       DO ig=1,ngrid
    115          DO l=lmin(ig)+1,nlay
    116             IF ((fm(ig,l+1)+detr(ig,l))*ptimestep.gt.1.e-6*masse(ig,l)) THEN
     106         DO l=1,nlay
     107            IF ((fm(ig,l+1)+detr(ig,l))*ptimestep > 1.e-6*masse(ig,l)) THEN
    117108               qa(ig,l) = (fm(ig,l) * qa(ig,l-1) + entr(ig,l) * q(ig,l))      &
    118109               &        / (fm(ig,l+1) + detr(ig,l))
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_main.F90

    r2177 r2229  
    383383     
    384384      CALL thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,detr0,masse,           &
    385       &                 zhl,zdthladj,dummy,lmin,lmax)
     385      &                 zhl,zdthladj,dummy)
    386386     
    387387      DO l=1,nlay
     
    397397      DO iq=1,nq
    398398         CALL thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,detr0,masse,        &
    399          &                 pq(:,:,iq),pdqadj(:,:,iq),zqa(:,:,iq),lmin,lmax)
     399         &                 pq(:,:,iq),pdqadj(:,:,iq),zqa(:,:,iq))
    400400      ENDDO
    401401     
     
    409409      ELSE
    410410         CALL thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,detr0,masse,           &
    411          &                 zu,pduadj,zua,lmin,lmax)
     411         &                 zu,pduadj,zua)
    412412         CALL thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,detr0,masse,           &
    413          &                 zv,pdvadj,zva,lmin,lmax)
     413         &                 zv,pdvadj,zva)
    414414      ENDIF
    415415     
Note: See TracChangeset for help on using the changeset viewer.