Changeset 5716


Ignore:
Timestamp:
Jun 18, 2025, 11:46:38 AM (5 weeks ago)
Author:
aborella
Message:

Minor bug fixes (temperature and water conservation)

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

Legend:

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

    r5691 r5716  
    968968                        ENDIF
    969969
     970                        IF ( ok_ice_sedim ) THEN
     971                          qice_sedim = flsed(i) / ( paprs(i,k) - paprs(i,k+1) ) * RG * dtime
     972                          ! Add the ice that was sedimented, as it is not included in zqn
     973                          qlbef(i) = qlbef(i) + qice_sedim
     974                        ENDIF
     975
    970976                        num = -Tbef(i)+zt(i)+rneb(i,k)*((1-zfice(i))*RLVTT &
    971977                              +zfice(i)*RLSTT)/RCPD/(1.0+RVTMP2*(zq(i)+zmqc(i)))*qlbef(i)
     
    10861092            ENDIF
    10871093
    1088             ! Remove the ice that was sedimentated. As it is not included in zqn,
    1089             ! we only remove it from the total water
    10901094            IF ( ok_ice_sedim ) THEN
    1091               zq(i) = zq(i) - flsed(i) / ( paprs(i,k) - paprs(i,k+1) ) * RG * dtime
     1095              qice_sedim = flsed(i) / ( paprs(i,k) - paprs(i,k+1) ) * RG * dtime
     1096              ! Remove the ice that was sedimented. As it is not included in zqn,
     1097              ! we only remove it from the total water
     1098              zq(i) = zq(i) - qice_sedim
     1099              ! Temperature update due to phase change (sedimented ice was condensed)
     1100              zt(i) = zt(i) + qice_sedim &
     1101                    * RLSTT / RCPD / ( 1. + RVTMP2 * ( zq(i) + zmqc(i) + zcond(i) ) )
    10921102            ENDIF
    1093            
    1094            
     1103
    10951104            ! temperature update due to phase change
    10961105            zt(i) = zt(i) + (1.-zfice(i))*zcond(i) &
  • TabularUnified LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_condensation.f90

    r5691 r5716  
    133133USE lmdz_lscp_ini,   ONLY: beta_pdf_lscp, temp_thresh_pdf_lscp
    134134USE lmdz_lscp_ini,   ONLY: std100_pdf_lscp, k0_pdf_lscp, kappa_pdf_lscp
    135 USE lmdz_lscp_ini,   ONLY: coef_mixing_lscp, coef_shear_lscp
     135USE lmdz_lscp_ini,   ONLY: coef_mixing_lscp, coef_shear_lscp, chi_mixing
    136136USE lmdz_lscp_ini,   ONLY: aspect_ratio_cirrus, cooling_rate_ice_thresh
    137 USE lmdz_lscp_ini,   ONLY: ok_ice_sedim, fallice_sedim
     137USE lmdz_lscp_ini,   ONLY: ok_ice_sedim, fallice_sedim, cice_velo, dice_velo
     138USE lmdz_lscp_ini,   ONLY: chi_sedim
    138139
    139140USE lmdz_lscp_ini,   ONLY: ok_plane_contrail, aspect_ratio_lincontrails
     
    289290! for sedimentation
    290291REAL, DIMENSION(klon) :: cfsed_abv, qised_abv
    291 REAL :: qice_sedim
     292REAL :: iwc, icefall_velo, qice_sedim
    292293REAL :: sedfra_abv, sedfra1, sedfra2, sedfra3
    293294!
     
    732733        !--New PDF
    733734        rhl_clr = qclr(i) / clrfra(i) / qsatl(i) * 100.
    734         rhl_clr = MAX(0., MIN(150., rhl_clr))
     735        !--rhl_clr is limited to 80%, because the fit is not valid above.
     736        !--This corresponds to rhi_clr ~= 140% at 210K, and ~= 105% at 245K
     737        rhl_clr = MAX(0., MIN(80., rhl_clr))
    735738
    736739        !--Calculation of the properties of the PDF
     
    740743        !--Coefficient for standard deviation:
    741744        !--  tuning coef * (clear sky area**0.25) * (function of temperature)
    742         pdf_e1 = beta_pdf_lscp * ( clrfra(i) * cell_area(i) )**0.25 &
    743                 * MAX( MAX(205., MIN(250., temp(i))) - temp_thresh_pdf_lscp, 0. )
     745        !--MAX on the sqrt of the area because the parameterization was derived for
     746        !-- L > 50 km
     747        pdf_e1 = beta_pdf_lscp * SQRT(MAX(5e4, SQRT( clrfra(i) * cell_area(i) ) )) &
     748                * MAX( MAX(210., MIN(245., temp(i))) - temp_thresh_pdf_lscp, 0. )
    744749        IF ( rhl_clr .GT. 50. ) THEN
    745750          pdf_std = ( pdf_e1 - std100_pdf_lscp ) * ( 100. - rhl_clr ) / 50. + std100_pdf_lscp
     
    748753        ENDIF
    749754        pdf_e3 = k0_pdf_lscp + kappa_pdf_lscp * &
    750                     MAX( temp_nowater - MAX(205., MIN(250., temp(i))), 0. )
     755                    MAX( temp_nowater - MAX(210., MIN(245., temp(i))), 0. )
    751756        pdf_alpha(i) = EXP( rhl_clr / 100. ) * pdf_e3
    752757        pdf_alpha(i) = MIN(10., pdf_alpha(i)) !--Avoid overflows
     
    972977          !--This implies that ( 1. - sigma_mix ) quantifies the ratio where mixing
    973978          !--decreases the size of the clouds
    974           sigma_mix = pdf_fra_above_lim / ( pdf_fra_below_lim + pdf_fra_above_lim )
     979          !sigma_mix = pdf_fra_above_lim / ( pdf_fra_below_lim + pdf_fra_above_lim )
     980          !--The chance that the air surrounding cirrus clouds is moist is higher then
     981          !--the actual distribution of humidity in the gridbox.
     982          !--This is quantified with chi_mixing. For chi_mixing=1, the two are equal.
     983          !--If chi_mixing > 1, the chance that moist air is around cirrus clouds is increased
     984          sigma_mix = MAX(1. - pdf_fra_below_lim / clrfra_mix, &
     985                      MIN(pdf_fra_above_lim / clrfra_mix, &
     986                  chi_mixing * pdf_fra_above_lim &
     987                  / ( pdf_fra_below_lim + chi_mixing * pdf_fra_above_lim )))
    975988
    976989          IF ( pdf_fra_above_lim .GT. eps ) THEN
    977             dcf_mix(i)  = clrfra_mix * sigma_mix
    978             dqvc_mix(i) = clrfra_mix * sigma_mix * pdf_q_above_lim / pdf_fra_above_lim
     990            IF ( ok_unadjusted_clouds .AND. .NOT. ok_warm_cloud ) THEN
     991              dcf_mix(i)  = clrfra_mix * sigma_mix
     992              dqvc_mix(i) = clrfra_mix * sigma_mix * pdf_q_above_lim / pdf_fra_above_lim
     993            ELSE
     994              dcf_mix(i)  = clrfra_mix * sigma_mix
     995              dqvc_mix(i) = clrfra_mix * sigma_mix * qsat(i)
     996              dqi_mix(i)  = clrfra_mix * sigma_mix * (pdf_q_above_lim / pdf_fra_above_lim - qsat(i))
     997            ENDIF
    979998          ENDIF
    980999
     
    11301149          !--For aviation, we increase the chance that the air surrounding contrails
    11311150          !--is moist. This is quantified with chi_mixing_lincontrails
    1132           sigma_mix = chi_mixing_lincontrails * pdf_fra_above_lim &
    1133                     / ( pdf_fra_below_lim + chi_mixing_lincontrails * pdf_fra_above_lim )
     1151          sigma_mix = MAX(1. - pdf_fra_below_lim / clrfra_mix, &
     1152                      MIN(pdf_fra_above_lim / clrfra_mix, &
     1153                  chi_mixing_lincontrails * pdf_fra_above_lim &
     1154                  / ( pdf_fra_below_lim + chi_mixing_lincontrails * pdf_fra_above_lim )))
    11341155
    11351156          IF ( pdf_fra_above_lim .GT. eps ) THEN
     
    12901311          !--This implies that ( 1. - sigma_mix ) quantifies the ratio where mixing
    12911312          !--decreases the size of the clouds
    1292           sigma_mix = pdf_fra_above_lim / ( pdf_fra_below_lim + pdf_fra_above_lim )
     1313          sigma_mix = MAX(1. - pdf_fra_below_lim / clrfra_mix, &
     1314                      MIN(pdf_fra_above_lim / clrfra_mix, &
     1315                  chi_mixing * pdf_fra_above_lim &
     1316                  / ( pdf_fra_below_lim + chi_mixing * pdf_fra_above_lim )))
    12931317
    12941318          IF ( pdf_fra_above_lim .GT. eps ) THEN
     
    13621386        !--in-cloud ice water content is constant.
    13631387        !
    1364         qice_sedim = 0.
    13651388        IF ( cldfra(i) .GT. eps ) THEN
    1366           dzsed(i) = MIN(fallice_sedim * dtime, dz)
     1389          iwc = rho * ( qcld(i) - qvc(i) ) / cldfra(i)
     1390          icefall_velo = fallice_sedim * cice_velo * iwc**dice_velo
     1391          dzsed(i) = icefall_velo * dtime * MAX(0., MIN(1., (2. - icefall_velo * dtime / dz)))
    13671392          cfsed(i) = cldfra(i)
    13681393          qice_sedim = ( qcld(i) - qvc(i) ) * dzsed(i) / dz
     
    14331458                                + pdf_loc * pdf_fra_above_lim ) * qsatl(i) / 100.
    14341459            ENDIF
     1460           
     1461            sedfra1 = MAX(sedfra1 - pdf_fra_below_lim, MIN(pdf_fra_above_lim, &
     1462                    sedfra1 * chi_sedim * pdf_fra_above_lim &
     1463                    / ( pdf_fra_below_lim + chi_sedim * pdf_fra_above_lim )))
    14351464
    14361465            IF ( pdf_fra_above_lim .GT. eps ) THEN
    1437               sedfra1 = sedfra1 * pdf_fra_above_lim / clrfra(i)
    1438               dcf_sed(i)  = dcf_sed(i)  + sedfra1
    1439               dqvc_sed(i) = dqvc_sed(i) + sedfra1 * pdf_q_above_lim / pdf_fra_above_lim
    1440               dqi_sed(i)  = dqi_sed(i)  + sedfra1 * qiceincld
     1466              IF ( ok_unadjusted_clouds .AND. .NOT. ok_warm_cloud ) THEN
     1467                dcf_sed(i)  = dcf_sed(i)  + sedfra1
     1468                dqvc_sed(i) = dqvc_sed(i) + sedfra1 * pdf_q_above_lim / pdf_fra_above_lim
     1469                dqi_sed(i)  = dqi_sed(i)  + sedfra1 * qiceincld
     1470              ELSE
     1471                dcf_sed(i)  = dcf_sed(i)  + sedfra1
     1472                dqvc_sed(i) = dqvc_sed(i) + sedfra1 * qsat(i)
     1473                dqi_sed(i)  = dqi_sed(i)  + sedfra1 &
     1474                                 * (qiceincld + pdf_q_above_lim / pdf_fra_above_lim - qsat(i))
     1475              ENDIF
    14411476            ENDIF
    14421477          ENDIF ! ( sedfra1 .GT. eps .AND. ( clrfra(i) .GT. eps )
     
    14461481
    14471482          !--For region (3)
    1448           IF ( sedfra3 .GT. eps ) THEN
     1483          IF ( cldfra(i) .GT. eps ) THEN
    14491484            dcf_sed(i)  = dcf_sed(i)  + sedfra3
    14501485            dqvc_sed(i) = dqvc_sed(i) + sedfra3 * qvc(i) / cldfra(i)
     
    14521487          ENDIF
    14531488        ENDIF ! qised_abv(i) .GT. 0.
    1454         !PRINT *, 'A', cldfra(i), dcf_sed(i), clrfra(i)
    1455         !PRINT *, 'B', qcld(i) - qvc(i), qvc(i), dqvc_sed(i), dqi_sed(i)
    14561489
    14571490        !--Add tendencies
  • TabularUnified LMDZ6/branches/contrails/libf/phylmd/lmdz_lscp_ini.f90

    r5691 r5716  
    221221  REAL, SAVE, PROTECTED :: coef_shear_lscp=0.72              ! [-] additional coefficient for the shearing process (subprocess of the mixing process)
    222222  !$OMP THREADPRIVATE(coef_shear_lscp)
     223 
     224  REAL, SAVE, PROTECTED :: chi_mixing=1.5                    ! [-] factor for increasing the chance that moist air is surrounding  cirrus clouds
     225  !$OMP THREADPRIVATE(chi_mixing)
    223226  !--End of the parameters for condensation and ice supersaturation
    224227
     
    373376  REAL, SAVE, PROTECTED :: fallice_sedim=1.                 ! Tuning factor for ice fallspeed velocity for sedimentation [-]
    374377  !$OMP THREADPRIVATE(fallice_sedim)
     378 
     379  REAL, SAVE, PROTECTED :: chi_sedim=1E5                    ! [-] factor for increasing the chance that sedimented ice falls into moist air
     380  !$OMP THREADPRIVATE(chi_sedim)
    375381  !--End of the parameters for poprecip
    376382
     
    494500    CALL getin_p('ok_ice_sedim',ok_ice_sedim)
    495501    CALL getin_p('fallice_sedim',fallice_sedim)
     502    CALL getin_p('chi_sedim',chi_sedim)
    496503    ! for condensation and ice supersaturation
    497504    CALL getin_p('ok_unadjusted_clouds',ok_unadjusted_clouds)
     
    517524    CALL getin_p('coef_mixing_lscp',coef_mixing_lscp)
    518525    CALL getin_p('coef_shear_lscp',coef_shear_lscp)
     526    CALL getin_p('chi_mixing',chi_mixing)
    519527    ! for aviation
    520528    CALL getin_p('ok_precip_contrails',ok_precip_contrails)
     
    599607    WRITE(lunout,*) 'lscp_ini, ok_ice_sedim:', ok_ice_sedim
    600608    WRITE(lunout,*) 'lscp_ini, fallice_sedim:', fallice_sedim
     609    WRITE(lunout,*) 'lscp_ini, chi_sedim:', chi_sedim
    601610    ! for condensation and ice supersaturation
    602611    WRITE(lunout,*) 'lscp_ini, ok_ice_supersat:', ok_ice_supersat
     
    622631    WRITE(lunout,*) 'lscp_ini, coef_mixing_lscp:', coef_mixing_lscp
    623632    WRITE(lunout,*) 'lscp_ini, coef_shear_lscp:', coef_shear_lscp
     633    WRITE(lunout,*) 'lscp_ini, chi_mixing:', chi_mixing
    624634    ! for aviation
    625635    WRITE(lunout,*) 'lscp_ini, ok_precip_contrails:', ok_precip_contrails
Note: See TracChangeset for help on using the changeset viewer.