Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (6 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_tools.f90

    r5790 r5791  
    287287
    288288
    289 SUBROUTINE ICEFRAC_LSCP_TURB(klon, dtime, pticefracturb, temp, pplay, paprsdn, paprsup, wvel, qice_ini, snowcld, snowfracld, qtot_incl, cldfra, tke,   &
     289SUBROUTINE ICEFRAC_LSCP_TURB(klon, dtime, pticefracturb, temp, pplay, paprsdn, paprsup, wvel, qice_ini, snowcld, qtot_incl, cldfra, tke,   &
    290290                             tke_dissip, sursat_e, invtau_e, qliq, qvap_cld, qice, icefrac, dicefracdT, cldfraliq, sigma2_icefracturb, mean_icefracturb)
    291291!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
     
    321321   REAL,      INTENT(IN),       DIMENSION(klon)    :: qice_ini            !--initial specific ice content gridbox-mean     [kg/kg]
    322322   REAL,      INTENT(IN),       DIMENSION(klon)    :: snowcld             !--in-cloud snowfall flux                        [kg/m2/s]
    323    REAL,      INTENT(IN),       DIMENSION(klon)    :: snowfracld          !--cloudy precip fraction                        [-]
    324323   REAL,      INTENT(IN),       DIMENSION(klon)    :: sursat_e            !--environment supersaturation                   [-]
    325324   REAL,      INTENT(IN),       DIMENSION(klon)    :: invtau_e            !--inverse time-scale of mixing with environment [s-1]
     
    422421           ! we consider here the mean snowflake concentration in the mesh (not the in-cloud concentration)
    423422           ! when poprecip is active, it will be worth testing considering the incloud fraction, dividing
    424            ! by snowfracld     
     423           ! by znebprecipcld     
    425424           ! qiceini_incl  = qice_ini(i) / cldfra1D + &
    426425           !              gamma_snwretro * snowcld(i) * RG * dtime / ( paprsdn(i) - paprsup(i) )
Note: See TracChangeset for help on using the changeset viewer.