Ignore:
Timestamp:
Nov 12, 2019, 11:55:58 AM (5 years ago)
Author:
aboissinot
Message:

Cleanup thermal plums model subroutines
In thermcell_flux, "bidouilles" are modified:

  • now the plumes stop when the updraft fraction is greater than alpha_max
  • e > e_max is no longer permitted
  • b <= incoming mass flux is checked last
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_main.F90

    r2144 r2177  
    4242!    New detr and entre formulae (no longer alimentation)
    4343!    lmin can be greater than 1
    44 !    Mix every tracer (EN COURS)
    45 !    Old version of thermcell_dq is removed
    46 !    Alternative version thermcell_dv2 is removed
     44!    Mix every tracer
    4745!
    4846!===============================================================================
     
    6159!     -------
    6260     
    63       INTEGER ngrid, nlay, nq
    64      
    65       REAL ptimestep
    66       REAL pplay(ngrid,nlay)                    ! Layer pressure
    67       REAL pplev(ngrid,nlay+1)                  ! Level pressure
    68       REAL pphi(ngrid,nlay)                     ! Geopotential
    69      
    70       REAL pu(ngrid,nlay)                       ! Zonal wind
    71       REAL pv(ngrid,nlay)                       ! Meridional wind
    72       REAL pt(ngrid,nlay)                       ! Temperature
    73       REAL pq(ngrid,nlay,nq)                    ! Tracers mass mixing ratio
    74      
    75       LOGICAL firstcall
     61      INTEGER, INTENT(in) :: ngrid
     62      INTEGER, INTENT(in) :: nlay
     63      INTEGER, INTENT(in) :: nq
     64     
     65      REAL, INTENT(in) :: ptimestep
     66      REAL, INTENT(in) :: pplay(ngrid,nlay)           ! Layer pressure
     67      REAL, INTENT(in) :: pplev(ngrid,nlay+1)         ! Level pressure
     68      REAL, INTENT(in) :: pphi(ngrid,nlay)            ! Geopotential
     69     
     70      REAL, INTENT(in) :: pu(ngrid,nlay)              ! Zonal wind
     71      REAL, INTENT(in) :: pv(ngrid,nlay)              ! Meridional wind
     72      REAL, INTENT(in) :: pt(ngrid,nlay)              ! Temperature
     73      REAL, INTENT(in) :: pq(ngrid,nlay,nq)           ! Tracers mass mixing ratio
     74     
     75      LOGICAL, INTENT(in) :: firstcall
    7676     
    7777!     Outputs:
    7878!     --------
    7979     
    80       REAL pduadj(ngrid,nlay)                   ! u convective variations
    81       REAL pdvadj(ngrid,nlay)                   ! v convective variations
    82       REAL pdtadj(ngrid,nlay)                   ! t convective variations
    83       REAL pdqadj(ngrid,nlay,nq)                ! q convective variations
    84      
    85       REAL f0(ngrid)                            ! mass flux norm (after possible time relaxation)
    86       REAL fm0(ngrid,nlay+1)                    ! mass flux      (after possible time relaxation)
    87       REAL entr0(ngrid,nlay)                    ! entrainment    (after possible time relaxation)
    88       REAL detr0(ngrid,nlay)                    ! detrainment    (after possible time relaxation)
     80      INTEGER, INTENT(out) :: lmax(ngrid)             ! Highest layer reached by the plume
     81      INTEGER, INTENT(out) :: lmix(ngrid)             ! Layer in which plume vertical speed is maximal
     82      INTEGER, INTENT(out) :: lmin(ngrid)             ! First unstable layer
     83     
     84      REAL, INTENT(out) :: pduadj(ngrid,nlay)         ! u convective variations
     85      REAL, INTENT(out) :: pdvadj(ngrid,nlay)         ! v convective variations
     86      REAL, INTENT(out) :: pdtadj(ngrid,nlay)         ! t convective variations
     87      REAL, INTENT(out) :: pdqadj(ngrid,nlay,nq)      ! q convective variations
     88     
     89      REAL, INTENT(inout) :: f0(ngrid)                ! mass flux norm (after possible time relaxation)
     90      REAL, INTENT(inout) :: fm0(ngrid,nlay+1)        ! mass flux      (after possible time relaxation)
     91      REAL, INTENT(inout) :: entr0(ngrid,nlay)        ! entrainment    (after possible time relaxation)
     92      REAL, INTENT(inout) :: detr0(ngrid,nlay)        ! detrainment    (after possible time relaxation)
    8993     
    9094!     Local:
     
    9296     
    9397      INTEGER ig, k, l, iq
    94       INTEGER lmax(ngrid)                       ! Highest layer reached by the plume
    95       INTEGER lmix(ngrid)                       ! Layer in which plume vertical speed is maximal
    96       INTEGER lmin(ngrid)                       ! First unstable layer
    97      
    98       REAL zmix(ngrid)                          ! Altitude of maximal vertical speed
    99       REAL zmax(ngrid)                          ! Maximal altitudes where plumes are active
    100       REAL zmin(ngrid)                          ! Minimal altitudes where plumes are active
    101      
    102       REAL zlay(ngrid,nlay)                     ! Layers altitudes
    103       REAL zlev(ngrid,nlay+1)                   ! Levels altitudes
    104       REAL rho(ngrid,nlay)                      ! Layers densities
    105       REAL rhobarz(ngrid,nlay)                  ! Levels densities
    106       REAL masse(ngrid,nlay)                    ! Layers masses
    107       REAL zpopsk(ngrid,nlay)                   ! Exner function
    108      
    109       REAL zu(ngrid,nlay)                       ! u    environment
    110       REAL zv(ngrid,nlay)                       ! v    environment
    111       REAL zt(ngrid,nlay)                       ! TR   environment
    112       REAL zqt(ngrid,nlay)                      ! qt   environment
    113       REAL zql(ngrid,nlay)                      ! ql   environment
    114       REAL zhl(ngrid,nlay)                      ! TP   environment
    115       REAL ztv(ngrid,nlay)                      ! TRPV environment
    116       REAL zqs(ngrid,nlay)                      ! qsat environment
    117      
    118       REAL zua(ngrid,nlay)                      ! u    plume
    119       REAL zva(ngrid,nlay)                      ! v    plume
    120       REAL zta(ngrid,nlay)                      ! TR   plume
    121       REAL zqla(ngrid,nlay)                     ! qv   plume
    122       REAL zqta(ngrid,nlay)                     ! qt   plume
    123       REAL zhla(ngrid,nlay)                     ! TP   plume
    124       REAL ztva(ngrid,nlay)                     ! TRPV plume
    125       REAL zqsa(ngrid,nlay)                     ! qsat plume
    126      
    127       REAL zqa(ngrid,nlay,nq)                   ! q    plume (ql=0, qv=qt)
    128      
    129       REAL f_star(ngrid,nlay+1)                 ! Normalized mass flux
    130       REAL entr_star(ngrid,nlay)                ! Normalized entrainment (E* = e* dz)
    131       REAL detr_star(ngrid,nlay)                ! Normalized detrainment (D* = d* dz)
    132      
    133       REAL fm(ngrid,nlay+1)                     ! Mass flux
    134       REAL entr(ngrid,nlay)                     ! Entrainment (E = e dz)
    135       REAL detr(ngrid,nlay)                     ! Detrainment (D = d dz)
    136      
    137       REAL f(ngrid)                             ! Mass flux norm
    138       REAL lambda                               ! Time relaxation coefficent
    139       REAL fraca(ngrid,nlay+1)                  ! Updraft fraction
    140       REAL linter(ngrid)                        ! Level (continuous) of maximal vertical speed
    141       REAL wmax(ngrid)                          ! Maximal vertical speed
    142       REAL zw2(ngrid,nlay+1)                    ! Plume vertical speed
    143       REAL zdthladj(ngrid,nlay)                 ! Potential temperature variations
    144       REAL dummy(ngrid,nlay)                    ! Dummy argument for thermcell_dq()
     98     
     99      REAL zmix(ngrid)                                ! Altitude of maximal vertical speed
     100      REAL zmax(ngrid)                                ! Maximal altitudes where plumes are active
     101      REAL zmin(ngrid)                                ! Minimal altitudes where plumes are active
     102     
     103      REAL zlay(ngrid,nlay)                           ! Layers altitudes
     104      REAL zlev(ngrid,nlay+1)                         ! Levels altitudes
     105      REAL rho(ngrid,nlay)                            ! Layers densities
     106      REAL rhobarz(ngrid,nlay)                        ! Levels densities
     107      REAL masse(ngrid,nlay)                          ! Layers masses
     108      REAL zpopsk(ngrid,nlay)                         ! Exner function
     109     
     110      REAL zu(ngrid,nlay)                             ! u    environment
     111      REAL zv(ngrid,nlay)                             ! v    environment
     112      REAL zt(ngrid,nlay)                             ! TR   environment
     113      REAL zqt(ngrid,nlay)                            ! qt   environment
     114      REAL zql(ngrid,nlay)                            ! ql   environment
     115      REAL zhl(ngrid,nlay)                            ! TP   environment
     116      REAL ztv(ngrid,nlay)                            ! TRPV environment
     117      REAL zqs(ngrid,nlay)                            ! qsat environment
     118     
     119      REAL zua(ngrid,nlay)                            ! u    plume
     120      REAL zva(ngrid,nlay)                            ! v    plume
     121      REAL zqla(ngrid,nlay)                           ! qv   plume
     122      REAL zqta(ngrid,nlay)                           ! qt   plume
     123      REAL zhla(ngrid,nlay)                           ! TP   plume
     124      REAL ztva(ngrid,nlay)                           ! TRPV plume
     125      REAL zqsa(ngrid,nlay)                           ! qsat plume
     126     
     127      REAL zqa(ngrid,nlay,nq)                         ! q    plume (ql=0, qv=qt)
     128     
     129      REAL f_star(ngrid,nlay+1)                       ! Normalized mass flux
     130      REAL entr_star(ngrid,nlay)                      ! Normalized entrainment (E* = e* dz)
     131      REAL detr_star(ngrid,nlay)                      ! Normalized detrainment (D* = d* dz)
     132     
     133      REAL fm(ngrid,nlay+1)                           ! Mass flux
     134      REAL entr(ngrid,nlay)                           ! Entrainment (E = e dz)
     135      REAL detr(ngrid,nlay)                           ! Detrainment (D = d dz)
     136     
     137      REAL f(ngrid)                                   ! Mass flux norm
     138      REAL lambda                                     ! Time relaxation coefficent
     139      REAL fraca(ngrid,nlay+1)                        ! Updraft fraction
     140      REAL wmax(ngrid)                                ! Maximal vertical speed
     141      REAL zw2(ngrid,nlay+1)                          ! Plume vertical speed
     142      REAL zdthladj(ngrid,nlay)                       ! Potential temperature variations
     143      REAL dummy(ngrid,nlay)                          ! Dummy argument for thermcell_dq()
    145144     
    146145!===============================================================================
     
    154153      ENDIF
    155154     
    156       f_star(:,:) = 0.
    157       entr_star(:,:) = 0.
    158       detr_star(:,:) = 0.
    159      
    160       f(:) = 0.
    161      
    162       fm(:,:) = 0.
    163       entr(:,:) = 0.
    164       detr(:,:) = 0.
    165      
    166       lmax(:) = 1
    167       lmix(:) = 1
    168       lmin(:) = 1
     155      DO ig=1,ngrid
     156! AB: Minimal f0 value is set to 0. (instead of 1.e-2 in Earth version)
     157         f0(ig) = MAX(f0(ig), 0.)
     158      ENDDO
    169159     
    170160      pduadj(:,:) = 0.0
     
    173163      pdqadj(:,:,:) = 0.0
    174164     
    175       DO ig=1,ngrid
    176 ! AB: Careful: Hard-coded value from Earth version!
    177 !         f0(ig) = max(f0(ig), 1.e-2)
    178 ! AB: No pescribed minimal value for f0
    179          f0(ig) = max(f0(ig), 0.)
    180       ENDDO
     165      zdthladj(:,:) = 0.0
    181166     
    182167!===============================================================================
     
    212197      rho(:,:) = pplay(:,:) / (zpopsk(:,:) * RD * ztv(:,:))
    213198     
     199      rhobarz(:,1) = rho(:,1)
    214200      IF (prt_level.ge.10) THEN
    215201         print *, 'WARNING: density in the first layer is equal to density at the first level!'
    216          print *, 'rhobarz(:,1)', rhobarz(:,1)
    217          print *, 'rho(:,1)    ', rho(:,1)
    218       ENDIF
    219      
    220       rhobarz(:,1) = rho(:,1)
     202      ENDIF
    221203     
    222204      DO l=2,nlay
     
    244226!                               
    245227!     ---------------------------
    246 !                                        _
    247 !     ----- F_lmax+1=0 ------zmax         \
    248 !     lmax                                 |
    249 !     ------F_lmax>0-------------          |
    250 !                                          |
    251 !     ---------------------------          |
    252 !                                          |
    253 !     ---------------------------          |
    254 !                                          |
    255 !     ------------------wmax,zmix          |
    256 !     lmix                                 |
    257 !     ---------------------------          |
    258 !                                          |
    259 !     ---------------------------          |
    260 !                                          | E, D
    261 !     ---------------------------          |
    262 !                                          |
     228!                                       _
     229!     ----- F_lmax+1=0 ------zmax        \
     230!     lmax                                |
     231!     ------F_lmax>0-------------         |
     232!                                         |
     233!     ---------------------------         |
     234!                                         |
     235!     ---------------------------         |
     236!                                         |
     237!     ------------------wmax,zmix         |
     238!     lmix                                |
     239!     ---------------------------         |
     240!                                         |
     241!     ---------------------------         |
     242!                                         | E, D
     243!     ---------------------------         |
     244!                                         |
    263245!     --------------------------- rhobarz, f_star, fm, fm0, zw2, fraca
    264 !         zt, zu, zv, zo, rho              |
    265 !     ---------------------------          |
    266 !                                          |
    267 !     ---------------------------          |
    268 !                                          |
    269 !     ---------------------------          |
    270 !                                          |
    271 !     ------F_lmin+1>0-----------          |
    272 !     lmin                                 |
    273 !     ----- F_lmin=0 ------------        _/
     246!         zt, zu, zv, zo, rho             |
     247!     ---------------------------         |
     248!                                         |
     249!     ---------------------------         |
     250!                                         |
     251!     ---------------------------         |
     252!                                         |
     253!     ------F_lmin+1>0-----------         |
     254!     lmin                                |
     255!     ----- F_lmin=0 ------------       _/
    274256!                               
    275257!     ---------------------------
     
    309291!-------------------------------------------------------------------------------
    310292     
    311       CALL thermcell_plume(ngrid,nlay,nq,ptimestep,ztv,                       &
    312       &                    zhl,zqt,zql,rhobarz,zlev,pplev,pphi,zpopsk,        &
     293      CALL thermcell_plume(ngrid,nlay,nq,ptimestep,                           &
     294      &                    ztv,zhl,zqt,zql,zlev,pplev,zpopsk,                 &
    313295      &                    detr_star,entr_star,f_star,                        &
    314       &                    ztva,zhla,zqla,zqta,zta,zqsa,                      &
    315       &                    zw2,lmix,lmin)
     296      &                    ztva,zhla,zqta,zqla,zqsa,                          &
     297      &                    zw2,lmin)
    316298     
    317299!-------------------------------------------------------------------------------
     
    320302     
    321303! AB: Careful, zw2 became its square root in thermcell_height!
    322       CALL thermcell_height(ngrid,nlay,lmin,linter,lmix,lmax,zw2,             &
    323       &                     zlev,zmin,zmix,zmax,wmax,f_star)
     304      CALL thermcell_height(ngrid,nlay,lmin,lmix,lmax,zlev,                   &
     305      &                     zmin,zmix,zmax,zw2,wmax,f_star)
    324306     
    325307!===============================================================================
     
    341323      ENDIF
    342324     
    343 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    344 ! Test valable seulement en 1D mais pas genant
    345 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
     325! FH: Test valable seulement en 1D mais pas genant
    346326      IF (.not. (f0(1).ge.0.) ) THEN
    347327         print *, 'ERROR: mass flux norm is not positive!'
     
    403383     
    404384      CALL thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,detr0,masse,           &
    405       &                 zhl,zdthladj,dummy,lmin)
     385      &                 zhl,zdthladj,dummy,lmin,lmax)
    406386     
    407387      DO l=1,nlay
     
    417397      DO iq=1,nq
    418398         CALL thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,detr0,masse,        &
    419          &                 pq(:,:,iq),pdqadj(:,:,iq),zqa(:,:,iq),lmin)
     399         &                 pq(:,:,iq),pdqadj(:,:,iq),zqa(:,:,iq),lmin,lmax)
    420400      ENDDO
    421401     
     
    429409      ELSE
    430410         CALL thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,detr0,masse,           &
    431          &                 zu,pduadj,zua,lmin)
     411         &                 zu,pduadj,zua,lmin,lmax)
    432412         CALL thermcell_dq(ngrid,nlay,ptimestep,fm0,entr0,detr0,masse,           &
    433          &                 zv,pdvadj,zva,lmin)
     413         &                 zv,pdvadj,zva,lmin,lmax)
    434414      ENDIF
    435415     
Note: See TracChangeset for help on using the changeset viewer.