Ignore:
Timestamp:
Jan 18, 2019, 12:27:10 PM (6 years ago)
Author:
aboissinot
Message:

f0 is now allocated only if calltherm=true.
Useless thermal plume model flag "iflag_thermals_alim" is removed.

Location:
trunk/LMDZ.GENERIC/libf/phystd
Files:
4 edited

Legend:

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

    r2067 r2069  
    704704         if (calltherm) then
    705705            call init_thermcell_mod(g, rcp, r, pi, T_h2o_ice_liq, RV)
    706          endif
    707          
    708          ALLOCATE(f0(ngrid))
     706            ALLOCATE(f0(ngrid))
     707         endif
    709708         
    710709         call su_watercycle ! even if we don't have a water cycle, we might
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_alim.F90

    r2066 r2069  
    22!
    33!
    4       SUBROUTINE thermcell_alim(flag,ngrid,klev,ztv,zlev,alim_star,           &
    5                                 lalim,lmin)
     4      SUBROUTINE thermcell_alim(ngrid,klev,ztv,zlev,alim_star,lalim,lmin)
    65     
    76     
     
    2726      INTEGER, INTENT(IN) :: klev
    2827      INTEGER, INTENT(IN) :: lmin(ngrid)        ! plume initial level
    29       INTEGER, INTENT(IN) :: flag               ! useless here
    3028     
    3129      REAL, INTENT(IN) :: ztv(ngrid,klev)       ! Large scale virtual potential temperature
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_mod.F90

    r2066 r2069  
    88INTEGER,PARAMETER :: iflag_thermals_optflux     = 0         !     0
    99INTEGER,PARAMETER :: iflag_thermals_closure     = 2         !     2
    10 INTEGER,PARAMETER :: iflag_thermals_alim        = 0         !     0
    1110INTEGER,PARAMETER :: iflag_thermals             = 18        !     18
    1211
  • trunk/LMDZ.GENERIC/libf/phystd/thermcell_plume.F90

    r2066 r2069  
    1212!==============================================================================
    1313! thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance
     14! AB : ql means "liquid water mass mixing ratio"
     15!      qt means "total water mass mixing ratio"
     16!      TP means "potential temperature"
     17!      TRPV means "virtual potential temperature with latent heat release" 
     18!      TPV means "virtual potential temperature"
     19!      TR means "temperature with latent heat release"
    1420!==============================================================================
    1521     
     
    8692      REAL zqla_est(ngrid,klev)                 ! ql   plume (before mixing)
    8793      REAL zta_est(ngrid,klev)                  ! TR   plume (before mixing)
    88       REAL zbuoy(ngrid,klev)                    ! B    plume
    89       REAL zbuoyjam(ngrid,klev)                 ! B    plume (modified)
     94      REAL zbuoy(ngrid,klev)                    ! plume buoyancy
     95      REAL zbuoyjam(ngrid,klev)                 ! plume buoyancy (modified)
    9096     
    9197      REAL ztemp(ngrid)                         ! temperature for saturation vapor pressure computation in plume
     
    125131      zbetalpha = betalpha / (1. + betalpha)
    126132     
    127       ztva(:,:)        = ztv(:,:)               ! ztva     is set to the virtual potential temperature withour latent heat release
    128       ztva_est(:,:)    = ztva(:,:)              ! ztva_est is set to the virtual potential temperature withour latent heat release
     133      ztva(:,:)        = ztv(:,:)               ! ztva     is set to the virtual potential temperature without latent heat release
     134      ztva_est(:,:)    = ztva(:,:)              ! ztva_est is set to the virtual potential temperature without latent heat release
    129135      ztla(:,:)        = zthl(:,:)              ! ztla     is set to the potential temperature
    130136      zqta(:,:)        = po(:,:)                ! zqta     is set to qt
    131137      zqla(:,:)        = 0.                     ! zqla     is set to ql
    132138      zqla_est(:,:)    = 0.                     ! zqla_est is set to ql
    133       zha(:,:)         = ztva(:,:)              ! zha      is set to the plume virtual potential temperature withour latent heat release
     139      zha(:,:)         = ztva(:,:)              ! zha      is set to the plume virtual potential temperature without latent heat release
    134140     
    135141      zqsat(:)         = 0.
     
    180186! AB : On pourrait n'appeler thermcell_alim que si la plume est active
    181187!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    182       CALL thermcell_alim(iflag_thermals_alim,ngrid,klev,ztv,zlev,alim_star,  &
    183       &                   lalim,lmin)
     188      CALL thermcell_alim(ngrid,klev,ztv,zlev,alim_star,lalim,lmin)
    184189     
    185190!==============================================================================
Note: See TracChangeset for help on using the changeset viewer.