Changeset 5615 for LMDZ6/branches


Ignore:
Timestamp:
Apr 14, 2025, 11:29:13 PM (3 months ago)
Author:
aborella
Message:

Comments + small bugfixes

Location:
LMDZ6/branches/contrails/libf/phylmd
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails/libf/phylmd/lmdz_aviation.f90

    r5613 r5615  
    179179        pdf_q_above_qcritcont = 0.
    180180      ELSEIF ( pdf_y .LT. -10. ) THEN
    181         pdf_fra_above_qcritcont = 1.
    182         pdf_q_above_qcritcont = qclr(i) / clrfra(i)
     181        pdf_fra_above_qcritcont = clrfra(i)
     182        pdf_q_above_qcritcont = qclr(i)
    183183      ELSE
    184184        pdf_y = EXP( pdf_y )
     
    196196        pdf_q_above_qsat = 0.
    197197      ELSEIF ( pdf_y .LT. -10. ) THEN
    198         pdf_fra_above_qsat = 1.
    199         pdf_q_above_qsat = qclr(i) / clrfra(i)
     198        pdf_fra_above_qsat = clrfra(i)
     199        pdf_q_above_qsat = qclr(i)
    200200      ELSE
    201201        pdf_y = EXP( pdf_y )
  • LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp.f90

    r5609 r5615  
    334334  REAL, DIMENSION(klon) :: contfra, perscontfra, qcont
    335335  LOGICAL, DIMENSION(klon) :: pt_pron_clds
    336   !--Added for ice supersaturation (ok_ice_supersat) and contrails (ok_plane_contrail)
    337   ! Constants used for calculating ratios that are advected (using a parent-child
    338   ! formalism). This is not done in the dynamical core because at this moment,
    339   ! only isotopes can use this parent-child formalism. Note that the two constants
    340   ! are the same as the one use in the dynamical core, being also defined in
    341   ! dyn3d_common/infotrac.F90
    342   REAL :: min_qParent, min_ratio
    343336  !--for Lamquin et al 2012 diagnostics
    344337  REAL, DIMENSION(klon) :: issrfra100to150UP, issrfra150to200UP, issrfra200to250UP
     
    446439qvc(:)          = 0.
    447440shear(:)        = 0.
    448 min_qParent     = 1.e-30
    449 min_ratio       = 1.e-16
     441pt_pron_clds(:) = .FALSE.
    450442
    451443!--for Lamquin et al (2012) diagnostics
  • LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_condensation.f90

    r5613 r5615  
    124124
    125125USE lmdz_lscp_ini,   ONLY: depo_coef_cirrus, capa_cond_cirrus, rho_ice
    126 USE lmdz_lscp_ini,   ONLY: mu_subl_pdf_lscp, beta_pdf_lscp, temp_thresh_pdf_lscp
     126USE lmdz_lscp_ini,   ONLY: N_ice_volume, corr_incld_depsub, nu_iwc_pdf_lscp
     127USE lmdz_lscp_ini,   ONLY: beta_pdf_lscp, temp_thresh_pdf_lscp
    127128USE lmdz_lscp_ini,   ONLY: std100_pdf_lscp, k0_pdf_lscp, kappa_pdf_lscp
    128 USE lmdz_lscp_ini,   ONLY: coef_mixing_lscp, coef_shear_lscp
     129USE lmdz_lscp_ini,   ONLY: coef_mixing_lscp, coef_shear_lscp, incld_ice_thresh
    129130
    130131USE lmdz_lscp_ini,   ONLY: ok_plane_contrail, aspect_ratio_contrails
     
    241242REAL :: pres_sat, kappa_depsub, tauinv_depsub
    242243REAL :: air_thermal_conduct, water_vapor_diff
    243 REAL :: N_ice
    244244!
    245245! for dissipation
     
    402402      !--HYPOTHESIS 1: the ice crystals are spherical, therefore
    403403      !-- mi = 4/3 * pi * rm_ice**3 * rho_ice
    404       !--HYPOTHESIS 2: the ice crystals are monodisperse with the
    405       !--initial radius rm_ice_0.
    406       !--NB. this is notably different than the assumption
    407       !--of a distributed qice in the cloud made in the sublimation process;
    408       !--should it be consistent?
     404      !--HYPOTHESIS 2: the ice crystals concentration is constant in the cloud
     405      !
     406      !--The equation in terms of q_ice is valide locally, and the local ice water content
     407      !--follows a Gamma distribution with a factor nu_iwc_pdf_lscp. Therefore, by
     408      !--integrating the local equation over the PDF (entire cloud), a correcting factor
     409      !--must be included, equal to
     410      !-- corr_incld_depsub = GAMMA(nu + 1/3) / GAMMA(nu) / nu**(1/3)
     411      !--NB. this is equal to about 0.9, hence the correction is not big
     412      !--NB. to lighten the calculated, corr_incld_depsub is calculated in lmdz_lscp_ini
    409413      !
    410414      !--As the deposition process does not create new ice crystals,
     
    412416      !--therefore the sublimation process does not destroy ice crystals
    413417      !--(or, in a limit case, it destroys all ice crystals), then
    414       !--Nice is a constant during the sublimation/deposition process.
    415       !-- dmi = dqi, et Nice = qi_0 / ( 4/3 RPI rm_ice_0**3 rho_ice )
     418      !--Nice is a constant during the sublimation/deposition process
     419      !--hence dmi = dqi
    416420      !
    417       !--The deposition equation then reads:
    418       !-- dqi/dt = alpha*4pi*capa_cond_cirrus*rm_ice*(qvc-qsat)/qsat / ( R_v*T/esi/Dv + Ls/ka/T * (Ls/R_v/T - 1) ) * Nice
    419       !-- dqi/dt = alpha*4pi*capa_cond_cirrus* (qi / qi_0)**(1/3) *rm_ice_0*(qvc-qsat)/qsat &
     421      !--The deposition equation then reads for qi the in-cloud ice water content:
     422      !-- dqi/dt = alpha*4pi*capa_cond_cirrus*rm_ice*(qvc-qsat)/qsat * corr_incld_depsub &
     423      !--            / ( R_v*T/esi/Dv + Ls/ka/T * (Ls/R_v/T - 1) ) * Nice
     424      !-- dqi/dt = alpha*4pi*capa_cond_cirrus*Nice*corr_incld_depsub &
     425      !--             / ( 4pi/3 N_ice rho_ice )**(1/3) &
    420426      !--             / ( R_v*T/esi/Dv + Ls/ka/T * (Ls*R_v/T - 1) ) &
    421       !--                         * qi_0 / ( 4/3 RPI rm_ice_0**3 rho_ice )
    422       !-- dqi/dt = qi**(1/3) * (qvc - qsat) * qi_0**(2/3) &
    423       !--  *alpha/qsat*capa_cond_cirrus/ (R_v*T/esi/Dv + Ls/ka/T*(Ls*R_v/T - 1)) / ( 1/3 rm_ice_0**2 rho_ice )
     427      !--             qi**(1/3) * (qvc - qsat) / qsat
    424428      !--and we have
    425       !-- dqvc/dt = - qi**(1/3) * (qvc - qsat) / kappa * alpha * qi_0**(2/3) / rm_ice_0**2
    426       !-- dqi/dt  =   qi**(1/3) * (qvc - qsat) / kappa * alpha * qi_0**(2/3) / rm_ice_0**2
    427       !--where kappa = 1/3*rho_ice/capa_cond_cirrus*qsat*(R_v*T/esi/Dv + Ls/ka/T*(Ls/R_v/T - 1))
     429      !-- dqvc/dt = - alpha * kappa(T) * qi**(1/3) * (qvc - qsat)
     430      !-- dqi/dt  =   alpha * kappa(T) * qi**(1/3) * (qvc - qsat)
    428431      !
    429432      !--This system of equations can be resolved with an exact
    430433      !--explicit numerical integration, having one variable resolved
    431       !--explicitly, the other exactly. The exactly resolved variable is
    432       !--the one decreasing, so it is qvc if the process is
    433       !--condensation, qi if it is sublimation.
     434      !--explicitly, the other exactly. qvc is always the variable solved exactly.
    434435      !
    435436      !--kappa is computed as an initialisation constant, as it depends only
     
    440441      !--This formula for water vapor diffusivity comes from Hall and Pruppacher (1976)
    441442      water_vapor_diff = 0.211 * ( temp(i) / RTT )**1.94 * ( 101325. / pplay(i) ) * 1.e-4
    442       !--Median ice crystal concentration [#/m3] in cirrus clouds from Kramer et al (2020)
    443       N_ice = 0.003 * 1e6
    444       !--NB. the greater kappa_depsub, the lower the efficiency of the
     443      !--NB. the greater kappa_depsub, the more efficient is the
    445444      !--deposition/sublimation process
    446       kappa_depsub = ( 4. / 3. * RPI * N_ice / rho * rho_ice )**(1./3.) &
    447                    * qsat(i) / ( 4. * RPI * capa_cond_cirrus * N_ice / rho ) &
    448                    * ( RV * temp(i) / water_vapor_diff / pres_sat &
     445      kappa_depsub = 4. * RPI * capa_cond_cirrus * N_ice_volume / rho * corr_incld_depsub &
     446                   / qsat(i) / ( 4. / 3. * RPI * N_ice_volume / rho * rho_ice )**(1./3.) &
     447                   / ( RV * temp(i) / water_vapor_diff / pres_sat &
    449448                     + RLSTT / air_thermal_conduct / temp(i) * ( RLSTT / RV / temp(i) - 1. ) )
    450449
     
    488487       
    489488        !--If the ice water content is too low, the cloud is purely sublimated
    490         IF ( qiceincld .LT. ( 0.005 * qsat(i) ) ) THEN
     489        IF ( qiceincld .LT. eps ) THEN
    491490          dcfa_sub(i) = - contfra(i)
    492491          dqia_sub(i) = - qiceincld * contfra(i)
     
    530529        ELSE
    531530
    532           !IF ( qiceincld .LT. ( 0.005 * qsat(i) ) ) THEN
    533           !  dcf_sub(i) = ( qiceincld / ( 0.005 * qsat(i) ) - 1. ) * cldfra(i)
    534           !  dqvc_sub(i) = qvapincld * dcf_sub(i)
    535 
    536           !  cldfra(i) = cldfra(i) + dcf_sub(i)
    537           !  qcld(i) = qcld(i) + dqvc_sub(i)
    538           !  qvc(i) = qvc(i) + dqvc_sub(i)
    539           !  clrfra(i) = MIN(1., clrfra(i) - dcf_sub(i))
    540           !  qclr(i) = qclr(i) - dqvc_sub(i)
    541           !ENDIF
     531          !--Cirrus clouds cannot have an in-cloud ice water content lower than
     532          !--incld_ice_thresh times the saturation
     533          IF ( qiceincld .LT. ( incld_ice_thresh * qsat(i) ) ) THEN
     534            dcf_sub(i) = ( qiceincld / ( incld_ice_thresh * qsat(i) ) - 1. ) * cldfra(i)
     535            dqvc_sub(i) = qvapincld * dcf_sub(i)
     536
     537            cldfra(i) = cldfra(i) + dcf_sub(i)
     538            qcld(i) = qcld(i) + dqvc_sub(i)
     539            qvc(i) = qvc(i) + dqvc_sub(i)
     540            clrfra(i) = MIN(1., clrfra(i) - dcf_sub(i))
     541            qclr(i) = qclr(i) - dqvc_sub(i)
     542          ENDIF
    542543
    543544          IF ( ok_unadjusted_clouds .AND. .NOT. ok_warm_cloud ) THEN
     
    571572
    572573          !--If the dissipation process must be activated
    573           !IF ( cldfra(i) .GT. eps ) THEN
    574574          IF ( qvapincld_new .GT. qvapincld ) THEN
    575575            !--Gamma distribution starting at qvapincld
    576             pdf_shape = ( mu_subl_pdf_lscp + 1. ) / qiceincld
     576            pdf_shape = nu_iwc_pdf_lscp / qiceincld
    577577            pdf_y = pdf_shape * ( qvapincld_new - qvapincld )
    578             pdf_e1 = GAMMAINC ( mu_subl_pdf_lscp + 1. , pdf_y )
    579             pdf_e2 = GAMMAINC ( mu_subl_pdf_lscp + 2. , pdf_y )
     578            pdf_e1 = GAMMAINC ( nu_iwc_pdf_lscp      , pdf_y )
     579            pdf_e2 = GAMMAINC ( nu_iwc_pdf_lscp + 1. , pdf_y )
    580580
    581581            !--Tendencies and diagnostics
     
    649649        !--Coefficient for standard deviation:
    650650        !--  tuning coef * (clear sky area**0.25) * (function of temperature)
    651         !pdf_e1 = beta_pdf_lscp &
    652         !       * ( ( 1. - cldfra(i) ) * cell_area(i) )**( 1. / 4. ) &
    653         !       * MAX( temp(i) - temp_thresh_pdf_lscp, 0. )
    654         !--  tuning coef * (cell area**0.25) * (function of temperature)
    655651        pdf_e1 = beta_pdf_lscp * ( clrfra(i) * cell_area(i) )**0.25 &
    656652                * MAX( temp(i) - temp_thresh_pdf_lscp, 0. )
     
    873869            pdf_q_above_lim = 0.
    874870          ELSEIF ( pdf_y .LT. -10. ) THEN
    875             pdf_fra_above_lim = 1.
    876             pdf_q_above_lim = qclr(i) / clrfra(i)
     871            pdf_fra_above_lim = clrfra(i)
     872            pdf_q_above_lim = qclr(i)
    877873          ELSE
    878874            pdf_y = EXP( pdf_y )
     
    10301026            pdf_q_above_lim = 0.
    10311027          ELSEIF ( pdf_y .LT. -10. ) THEN
    1032             pdf_fra_above_lim = 1.
    1033             pdf_q_above_lim = qclr(i) / clrfra(i)
     1028            pdf_fra_above_lim = clrfra(i)
     1029            pdf_q_above_lim = qclr(i)
    10341030          ELSE
    10351031            pdf_y = EXP( pdf_y )
     
    11031099      !
    11041100      !--If ice supersaturation is activated, the cloud properties are prognostic.
    1105       !--The falling ice is then considered a new cloud in the gridbox.
     1101      !--The falling ice is then partly considered a new cloud in the gridbox.
    11061102      !--BEWARE with this parameterisation, we can create a new cloud with a much
    11071103      !--different ice water content and water vapor content than the existing cloud
     
    11341130            pdf_q_above_lim = 0.
    11351131          ELSEIF ( pdf_y .LT. -10. ) THEN
    1136             pdf_fra_above_lim = 1.
    1137             pdf_q_above_lim = qclr(i) / clrfra(i)
     1132            pdf_fra_above_lim = clrfra(i)
     1133            pdf_q_above_lim = qclr(i)
    11381134          ELSE
    11391135            pdf_y = EXP( pdf_y )
     
    11591155          dqi_sed(i) = qice_sedim(i)
    11601156
    1161         ENDIF ! clrfra(i) .GT. eps
     1157        ENDIF ! ( clrfra_sed .GT. eps .AND. ( clrfra(i) .GT. eps )
    11621158
    11631159        !--Add tendencies
     
    11691165        qclr(i)    = qclr(i) - dqvc_sed(i) + qice_sedim(i) - dqi_sed(i)
    11701166
    1171       ENDIF ! qice_sedim(i) .GT. 0.
     1167      ENDIF ! icesed_flux(i) .GT. 0.
    11721168
    11731169
     
    11881184          qissr(i) = 0.
    11891185        ELSEIF ( pdf_y .LT. -10. ) THEN
    1190           issrfra(i) = 1.
    1191           qissr(i) = qclr(i) / clrfra(i)
     1186          issrfra(i) = clrfra(i)
     1187          qissr(i) = qclr(i)
    11921188        ELSE
    11931189          pdf_y = EXP( pdf_y )
     
    12321228      dqvc_sed(i) = dqvc_sed(i) / dtime
    12331229
    1234     ENDIF ! ( temp(i) .GT. temp_nowater ) .AND. .NOT. ok_weibull_warm_clouds
     1230    ENDIF ! pt_pron_clds(i)
    12351231
    12361232  ENDIF   ! end keepgoing
     
    13201316
    13211317    ENDIF ! keepgoing
    1322   ENDDO
     1318  ENDDO ! loop on klon
    13231319ENDIF ! ok_plane_contrail
    13241320
  • LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_ini.f90

    r5609 r5615  
    165165  !$OMP THREADPRIVATE(ffallv_issr)
    166166
     167  REAL, SAVE, PROTECTED :: incld_ice_thresh=1.E-3            ! [-] minimum in-cloud ice water content, relative to saturation
     168  !$OMP THREADPRIVATE(incld_ice_thresh)
     169
    167170  REAL, SAVE, PROTECTED :: depo_coef_cirrus=.7               ! [-] deposition coefficient for growth of ice crystals in cirrus clouds
    168171  !$OMP THREADPRIVATE(depo_coef_cirrus)
     
    171174  !$OMP THREADPRIVATE(capa_cond_cirrus)
    172175
    173   REAL, SAVE, PROTECTED :: mu_subl_pdf_lscp=1./3.            ! [-] factor for the ice distribution inside cirrus clouds
    174   !$OMP THREADPRIVATE(mu_subl_pdf_lscp)
    175  
    176   REAL, SAVE, PROTECTED :: beta_pdf_lscp=8.75E-4             ! [SI] tuning coefficient for the standard deviation of the PDF of water vapor in the clear sky region
     176  REAL, SAVE, PROTECTED :: N_ice_volume=3.E4                 ! [#/m3] ice crystal concentration in cirrus clouds (default value from  Kramer et al, 2020)
     177  !$OMP THREADPRIVATE(N_ice_volume)
     178
     179  REAL, SAVE, PROTECTED :: nu_iwc_pdf_lscp=4./3.             ! [-] shape factor for the ice distribution inside cirrus clouds
     180  !$OMP THREADPRIVATE(nu_iwc_pdf_lscp)
     181
     182  REAL, SAVE, PROTECTED :: corr_incld_depsub                 ! [-] correction factor for in-cloud IWC rather than local IWC in dep / sub process BEWARE NO GETIN (calculated automatically)
     183  !$OMP THREADPRIVATE(corr_incld_depsub)
     184 
     185  REAL, SAVE, PROTECTED :: beta_pdf_lscp=8.46E-4             ! [SI] tuning coefficient for the standard deviation of the PDF of water vapor in the clear sky region
    177186  !$OMP THREADPRIVATE(beta_pdf_lscp)
    178187 
     
    183192  !$OMP THREADPRIVATE(k0_pdf_lscp)
    184193 
    185   REAL, SAVE, PROTECTED :: kappa_pdf_lscp=0.0192             ! [] factor for the PDF fit of water vapor in UTLS
     194  REAL, SAVE, PROTECTED :: kappa_pdf_lscp=0.0192             ! [K-1] factor for the PDF fit of water vapor in UTLS
    186195  !$OMP THREADPRIVATE(kappa_pdf_lscp)
    187196 
     
    475484    ffallv_issr=ffallv_lsc
    476485    CALL getin_p('ffallv_issr',ffallv_issr)
     486    CALL getin_p('incld_ice_thresh',incld_ice_thresh)
    477487    CALL getin_p('depo_coef_cirrus',depo_coef_cirrus)
    478488    CALL getin_p('capa_cond_cirrus',capa_cond_cirrus)
    479     CALL getin_p('mu_subl_pdf_lscp',mu_subl_pdf_lscp)
     489    CALL getin_p('nu_iwc_pdf_lscp',nu_iwc_pdf_lscp)
    480490    CALL getin_p('beta_pdf_lscp',beta_pdf_lscp)
    481491    CALL getin_p('temp_thresh_pdf_lscp',temp_thresh_pdf_lscp)
     
    573583    WRITE(lunout,*) 'lscp_ini, ok_weibull_warm_clouds:', ok_weibull_warm_clouds
    574584    WRITE(lunout,*) 'lscp_ini, ffallv_issr', ffallv_issr
     585    WRITE(lunout,*) 'lscp_ini, incld_ice_thresh', incld_ice_thresh
    575586    WRITE(lunout,*) 'lscp_ini, depo_coef_cirrus:', depo_coef_cirrus
    576587    WRITE(lunout,*) 'lscp_ini, capa_cond_cirrus:', capa_cond_cirrus
    577     WRITE(lunout,*) 'lscp_ini, mu_subl_pdf_lscp:', mu_subl_pdf_lscp
     588    WRITE(lunout,*) 'lscp_ini, nu_iwc_pdf_lscp:', nu_iwc_pdf_lscp
    578589    WRITE(lunout,*) 'lscp_ini, beta_pdf_lscp:', beta_pdf_lscp
    579590    WRITE(lunout,*) 'lscp_ini, temp_thresh_pdf_lscp:', temp_thresh_pdf_lscp
     
    629640    ENDIF
    630641
     642    !--Calculated here to lighten calculations
     643    corr_incld_depsub = GAMMA(nu_iwc_pdf_lscp + 1./3.) / GAMMA(nu_iwc_pdf_lscp) &
     644                      / nu_iwc_pdf_lscp**(1./3.)
     645
    631646
    632647    !AA Temporary initialisation
Note: See TracChangeset for help on using the changeset viewer.