Skip to content

Commit

Permalink
eam/micro_p3.F90 was using qv_sat, which is gone.
Browse files Browse the repository at this point in the history
The scream version of micro_p3 appears to use qv_sat_dry wherever qv_sat was being
used before, so I just replaced all occurances of qv_sat with qv_sat_dry.
  • Loading branch information
jgfouca committed Jan 18, 2024
1 parent 97a5c31 commit 423bc74
Showing 1 changed file with 8 additions and 8 deletions.
16 changes: 8 additions & 8 deletions components/eam/src/physics/p3/eam/micro_p3.F90
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ module micro_p3
lookup_table_1a_dum1_c, rho_h2o, &
do_Cooper_inP3

use wv_sat_scream, only:qv_sat
use wv_sat_scream, only:qv_sat_dry

! Bit-for-bit math functions.
#ifdef SCREAM_CONFIG_IS_CMAKE
Expand Down Expand Up @@ -477,8 +477,8 @@ SUBROUTINE p3_main_part1(kts, kte, kbot, ktop, kdir, do_predict_nc, do_prescribe
!can be made consistent with E3SM definition of latent heat
rho(k) = dpres(k)/dz(k)/g ! pres(k)/(rd*t(k))
inv_rho(k) = 1._rtype/rho(k)
qv_sat_l(k) = qv_sat(t_atm(k),pres(k),0)
qv_sat_i(k) = qv_sat(t_atm(k),pres(k),1)
qv_sat_l(k) = qv_sat_dry(t_atm(k),pres(k),0)
qv_sat_i(k) = qv_sat_dry(t_atm(k),pres(k),1)

qv_supersat_i(k) = qv(k)/qv_sat_i(k)-1._rtype

Expand Down Expand Up @@ -2425,7 +2425,7 @@ subroutine ice_melting(rho,t_atm,pres,rhofaci, &
real(rtype) :: qsat0

if (qi_incld .ge.qsmall .and. t_atm.gt.T_zerodegc) then
qsat0 = qv_sat( T_zerodegc,pres,0 )
qsat0 = qv_sat_dry( T_zerodegc,pres,0 )

qi2qr_melt_tend = ((table_val_qi2qr_melting+table_val_qi2qr_vent_melt*bfb_cbrt(sc)*bfb_sqrt(rhofaci*rho/mu))*((t_atm- &
T_zerodegc)*kap-rho*latent_heat_vapor*dv*(qsat0-qv))*2._rtype*pi/latent_heat_fusion)*ni_incld
Expand Down Expand Up @@ -2475,7 +2475,7 @@ subroutine ice_cldliq_wet_growth(rho,t_atm,pres,rhofaci, &
real(rtype) :: qsat0, dum, dum1

if (qi_incld.ge.qsmall .and. qc_incld+qr_incld.ge.1.e-6_rtype .and. t_atm.lt.T_zerodegc) then
qsat0=qv_sat( T_zerodegc,pres,0 )
qsat0=qv_sat_dry( T_zerodegc,pres,0 )

qwgrth = ((table_val_qi2qr_melting + table_val_qi2qr_vent_melt*bfb_cbrt(sc)*bfb_sqrt(rhofaci*rho/mu))* &
2._rtype*pi*(rho*latent_heat_vapor*dv*(qsat0-qv)-(t_atm-T_zerodegc)* &
Expand Down Expand Up @@ -3095,21 +3095,21 @@ subroutine prevent_ice_overdepletion(pres,t_atm,qv,latent_heat_vapor,latent_heat
qtmp_all = qv - (qidep + qinuc + qinuc_cnt)*dt + (qi2qv_sublim_tend + qr2qv_evap_tend)*dt
ttmp_all = t_atm + ((qidep-qi2qv_sublim_tend+qinuc+qinuc_cnt)*latent_heat_sublim*inv_cp + (-qr2qv_evap_tend*latent_heat_vapor*inv_cp))*dt

qv_sat_l = qv_sat(ttmp_all,pres,0)
qv_sat_l = qv_sat_dry(ttmp_all,pres,0)

! If water vapor mass exceeds ice saturation value, we limit only source terms (e.g., sublimation, rain evp)
if(qtmp_all > qv_sat_l)then

! ... First, rain evaporation is limited to the sub-saturation defined by the water vapor sink terms (deposition, ice nucleation)
q_sink = qv - (qidep + qinuc + qinuc_cnt)*dt
t_sink = t_atm + ((qidep+qinuc+qinuc_cnt)*latent_heat_sublim*inv_cp)*dt
dumqv_sat_l = qv_sat(t_sink,pres,0)
dumqv_sat_l = qv_sat_dry(t_sink,pres,0)
qv_source_evp = qr2qv_evap_tend + qi2qv_sublim_tend
qrevp_satadj = (q_sink-dumqv_sat_l)/(1._rtype + bfb_square(latent_heat_vapor)*dumqv_sat_l/(cp*rv* bfb_square(t_sink) ))*inv_dt
qr2qv_evap_tend = qr2qv_evap_tend*min(1._rtype,max(0._rtype,-qrevp_satadj)/max(qv_source_evp, 1.e-20_rtype))

! ... Next, ice-sublimation is limited in the same way but with sublim LH
dumqv_sat_i = qv_sat(t_sink,pres,1)
dumqv_sat_i = qv_sat_dry(t_sink,pres,1)
qi2qv_sublim_satadj = (q_sink-dumqv_sat_i)/(1._rtype + bfb_square(latent_heat_sublim)*dumqv_sat_i/(cp*rv* bfb_square(t_sink) ))*inv_dt
qi2qv_sublim_tend = qi2qv_sublim_tend*min(1._rtype,max(0._rtype,-qi2qv_sublim_satadj)/max(qv_source_evp, 1.e-20_rtype))

Expand Down

0 comments on commit 423bc74

Please sign in to comment.