Skip to content

Commit

Permalink
use physical constants from host for Thompson MP
Browse files Browse the repository at this point in the history
  • Loading branch information
grantfirl committed Feb 28, 2024
1 parent 61ef1d9 commit 716abb6
Show file tree
Hide file tree
Showing 4 changed files with 154 additions and 28 deletions.
62 changes: 39 additions & 23 deletions physics/MP/Thompson/module_mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -75,8 +75,8 @@ module module_mp_thompson
logical, parameter, private :: homogIce = .true.

integer, parameter, private :: IFDRY = 0
real(wp), parameter, private :: T_0 = 273.15
real(wp), parameter, private :: PI = 3.1415926536
real(wp) :: T_0 !set in mp_thompson_init from host model
real(wp) :: PI !set in mp_thompson_init from host model

!..Densities of rain, snow, graupel, and cloud ice.
real(wp), parameter, private :: rho_w = 1000.0
Expand Down Expand Up @@ -131,13 +131,13 @@ module module_mp_thompson

!..Mass power law relations: mass = am*D**bm
!.. Snow from Field et al. (2005), others assume spherical form.
real(wp), parameter, private :: am_r = PI*rho_w/6.0
real(wp), private :: am_r !set in thompson_init
real(wp), parameter, private :: bm_r = 3.0
real(wp), parameter, private :: am_s = 0.069
real(wp), parameter, private :: bm_s = 2.0
real(wp), parameter, private :: am_g = PI*rho_g/6.0
real(wp), private :: am_g !set in thompson_init
real(wp), parameter, private :: bm_g = 3.0
real(wp), parameter, private :: am_i = PI*rho_i/6.0
real(wp), private :: am_i !set in thompson_init
real(wp), parameter, private :: bm_i = 3.0

!..Fallspeed power laws relations: v = (av*D**bv)*exp(-fv*D)
Expand Down Expand Up @@ -181,7 +181,7 @@ module module_mp_thompson
real(wp), parameter, private :: ATO = 0.304

!..Rho_not used in fallspeed relations (rho_not/rho)**.5 adjustment.
real(wp), parameter, private :: rho_not = 101325.0 / (287.05*298.0)
real(wp) :: rho_not !set in thompson_init

!..Schmidt number
real(wp), parameter, private :: Sc = 0.632
Expand All @@ -191,25 +191,25 @@ module module_mp_thompson
real(wp), parameter, private:: HGFR = 235.16

!..Water vapor and air gas constants at constant pressure
real(wp), parameter, private :: Rv = 461.5
real(wp), parameter, private :: oRv = 1./Rv
real(wp), parameter, private :: R = 287.04
real(wp), parameter, private :: RoverRv = R*oRv
real(wp), parameter, private :: Cp = 1004.0
real(wp), parameter, private :: R_uni = 8.314 !< J (mol K)-1

real(dp), parameter, private :: k_b = 1.38065e-23 !< Boltzmann constant [J/K]
real(dp), parameter, private :: M_w = 18.01528e-3 !< molecular mass of water [kg/mol]
real(dp), parameter, private :: M_a = 28.96e-3 !< molecular mass of air [kg/mol]
real(dp), parameter, private :: N_avo = 6.022e23 !< Avogadro number [1/mol]
real(dp), parameter, private :: ma_w = M_w / N_avo !< mass of water molecule [kg]
real(wp), parameter, private :: ar_volume = 4./3.*PI*(2.5e-6)**3 !< assume radius of 0.025 micrometer, 2.5e-6 cm
real(wp) :: Rv !set in mp_thompson_init from host model
real(wp), private :: oRv !set in thompson_init
real(wp) :: R !set in mp_thompson_init from host model
real(wp) :: RoverRv !set in mp_thompson_init from host model
real(wp) :: Cp !set in mp_thompson_init from host model
real(wp) :: R_uni !set in mp_thompson_init from host model

real(dp) :: k_b !set in mp_thompson_init from host model !< Boltzmann constant [J/K]
real(dp) :: M_w !set in mp_thompson_init from host model !< molecular mass of water [kg/mol]
real(dp) :: M_a !set in mp_thompson_init from host model !< molecular mass of air [kg/mol]
real(dp) :: N_avo !set in mp_thompson_init from host model !< Avogadro number [1/mol]
real(dp), private :: ma_w !set in thompson_init !< mass of water molecule [kg]
real(wp), private :: ar_volume !set in thompson_init

!..Enthalpy of sublimation, vaporization, and fusion at 0C.
real(wp), parameter, private :: lsub = 2.834e6
real(wp), parameter, private :: lvap0 = 2.5e6
real(wp), parameter, private :: lfus = lsub - lvap0
real(wp), parameter, private :: olfus = 1./lfus
real(wp), private :: lsub !set in thompson_init
real(wp) :: lvap0 !set in mp_thompson_init from host model
real(wp) :: lfus !set in mp_thompson_init from host model
real(wp), private :: olfus !set in thompson_init

!..Ice initiates with this mass (kg), corresponding diameter calc.
!..Min diameters and mass of cloud, rain, snow, and graupel (m, kg).
Expand Down Expand Up @@ -456,6 +456,22 @@ subroutine thompson_init(is_aerosol_aware_in, &
real(wp) :: stime, etime
logical, parameter :: precomputed_tables = .FALSE.

! Set module derived constants
am_r = PI*rho_w/6.0
am_g = PI*rho_g/6.0
am_i = PI*rho_i/6.0

ar_volume = 4./3.*PI*(2.5e-6)**3 !< assume radius of 0.025 micrometer, 2.5e-6 cm

rho_not = 101325.0 / (R*298.0)

oRv = 1./Rv

ma_w = M_w / N_avo

lsub = lvap0 + lfus
olfus = 1./lfus

! Set module variable is_aerosol_aware/merra2_aerosol_aware
is_aerosol_aware = is_aerosol_aware_in
merra2_aerosol_aware = merra2_aerosol_aware_in
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@
!>\ingroup aathompson
module module_mp_thompson_make_number_concentrations

use physcons, only: PI => con_pi
use module_mp_thompson, only: PI

implicit none

Expand Down
30 changes: 26 additions & 4 deletions physics/MP/Thompson/mp_thompson.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@
module mp_thompson

use machine, only : kind_phys

use module_mp_thompson, only : thompson_init, mp_gt_driver, thompson_finalize, calc_effectRad
use module_mp_thompson, only : naIN0, naIN1, naCCN0, naCCN1, eps, Nt_c_l, Nt_c_o
use module_mp_thompson, only : re_qc_min, re_qc_max, re_qi_min, re_qi_max, re_qs_min, re_qs_max
Expand All @@ -30,7 +30,10 @@ module mp_thompson
!! \section arg_table_mp_thompson_init Argument Table
!! \htmlinclude mp_thompson_init.html
!!
subroutine mp_thompson_init(ncol, nlev, con_g, con_rd, con_eps, &
subroutine mp_thompson_init(ncol, nlev, con_pi, con_t0c, con_rv, &
con_cp, con_rgas, con_boltz, con_amd, &
con_amw, con_avgd, con_hvap, con_hfus, &
con_g, con_rd, con_eps, &
restart, imp_physics, &
imp_physics_thompson, convert_dry_rho, &
spechum, qc, qr, qi, qs, qg, ni, nr, &
Expand All @@ -40,13 +43,17 @@ subroutine mp_thompson_init(ncol, nlev, con_g, con_rd, con_eps, &
aerfld, mpicomm, mpirank, mpiroot, &
threads, ext_diag, diag3d, &
errmsg, errflg)

use module_mp_thompson, only : PI, T_0, Rv, R, RoverRv, Cp
use module_mp_thompson, only : R_uni, k_b, M_w, M_a, N_avo, lvap0, lfus

implicit none

! Interface variables
integer, intent(in ) :: ncol
integer, intent(in ) :: nlev
real(kind_phys), intent(in ) :: con_g, con_rd, con_eps
real(kind_phys), intent(in ) :: con_pi, con_t0c, con_rv, con_cp, con_rgas, &
con_boltz, con_amd, con_amw, con_avgd, &
con_hvap, con_hfus, con_g, con_rd, con_eps
logical, intent(in ) :: restart
integer, intent(in ) :: imp_physics
integer, intent(in ) :: imp_physics_thompson
Expand Down Expand Up @@ -103,6 +110,21 @@ subroutine mp_thompson_init(ncol, nlev, con_g, con_rd, con_eps, &

if (is_initialized) return

! Set local Thompson MP module constants from host model
PI = con_pi
T_0 = con_t0c
Rv = con_Rv
R = con_rd
RoverRv = con_eps
Cp = con_cp
R_uni = con_rgas
k_b = con_boltz
M_w = con_amw*1.0E-3 !module_mp_thompson expects kg/mol
M_a = con_amd*1.0E-3 !module_mp_thompson expects kg/mol
N_avo = con_avgd
lvap0 = con_hvap
lfus = con_hfus

! Consistency checks
if (imp_physics/=imp_physics_thompson) then
write(errmsg,'(*(a))') "Logic error: namelist choice of microphysics is different from Thompson MP"
Expand Down
88 changes: 88 additions & 0 deletions physics/MP/Thompson/mp_thompson.meta
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,94 @@
dimensions = ()
type = integer
intent = in
[con_pi]
standard_name = pi
long_name = ratio of a circle's circumference to its diameter
units = none
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_t0c]
standard_name = temperature_at_zero_celsius
long_name = temperature at 0 degrees Celsius
units = K
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_rv]
standard_name = gas_constant_water_vapor
long_name = ideal gas constant for water vapor
units = J kg-1 K-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_cp]
standard_name = specific_heat_of_dry_air_at_constant_pressure
long_name = specific heat of dry air at constant pressure
units = J kg-1 K-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_rgas]
standard_name = molar_gas_constant
long_name = universal ideal molar gas constant
units = J K-1 mol-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_boltz]
standard_name = boltzmann_constant
long_name = Boltzmann constant
units = J K-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_amd]
standard_name = molecular_weight_of_dry_air
long_name = molecular weight of dry air
units = g mol-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_amw]
standard_name = molecular_weight_of_water_vapor
long_name = molecular weight of water vapor
units = g mol-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_avgd]
standard_name = avogadro_consant
long_name = Avogadro constant
units = mol-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_hvap]
standard_name = latent_heat_of_vaporization_of_water_at_0C
long_name = latent heat of evaporation/sublimation
units = J kg-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_hfus]
standard_name = latent_heat_of_fusion_of_water_at_0C
long_name = latent heat of fusion
units = J kg-1
dimensions = ()
type = real
kind = kind_phys
intent = in
[con_g]
standard_name = gravitational_acceleration
long_name = gravitational acceleration
Expand Down

0 comments on commit 716abb6

Please sign in to comment.