Skip to content

Commit

Permalink
Merge branch 'ufs-community:ufs/dev' into feature/hafsv2_baseline_wit…
Browse files Browse the repository at this point in the history
…h_ssc
  • Loading branch information
binli2337 authored Jan 31, 2024
2 parents ae1f0ca + d52832b commit 1545c6b
Show file tree
Hide file tree
Showing 2 changed files with 137 additions and 6 deletions.
48 changes: 42 additions & 6 deletions physics/MP/NSSL/mp_nssl.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,7 @@ module mp_nssl

private
logical :: is_initialized = .False.
logical :: missing_vars_global = .False.
real :: nssl_qccn

contains
Expand All @@ -26,7 +27,9 @@ module mp_nssl
!! \htmlinclude mp_nssl_init.html
!!
subroutine mp_nssl_init(ncol, nlev, errflg, errmsg, threads, restart, &
mpirank, mpiroot, &
mpirank, mpiroot,mpicomm, &
qc, qr, qi, qs, qh, &
ccw, crw, cci, csw, chw, vh, &
con_g, con_rd, con_cp, con_rv, &
con_t0c, con_cliq, con_csol, con_eps, &
imp_physics, imp_physics_nssl, &
Expand All @@ -36,6 +39,9 @@ subroutine mp_nssl_init(ncol, nlev, errflg, errmsg, threads, restart, &


use module_mp_nssl_2mom, only: nssl_2mom_init, nssl_2mom_init_const
#ifdef MPI
use mpi
#endif

implicit none

Expand All @@ -50,16 +56,32 @@ subroutine mp_nssl_init(ncol, nlev, errflg, errmsg, threads, restart, &

integer, intent(in) :: mpirank
integer, intent(in) :: mpiroot
integer, intent(in) :: mpicomm
integer, intent(in) :: imp_physics
integer, intent(in) :: imp_physics_nssl
real(kind_phys), intent(in) :: nssl_cccn, nssl_alphah, nssl_alphahl
real(kind_phys), intent(in) :: nssl_alphar, nssl_ehw0, nssl_ehlw0
logical, intent(in) :: nssl_ccn_on, nssl_hail_on, nssl_invertccn, nssl_3moment

real(kind_phys), intent(inout) :: qc (:,:) !(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: qr (:,:) !(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: qi (:,:) !(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: qs (:,:) !(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: qh (:,:) !(1:ncol,1:nlev) graupel
real(kind_phys), intent(inout) :: ccw(:,:) !(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: crw(:,:) !(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: cci(:,:) !(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: csw(:,:) !(1:ncol,1:nlev)
real(kind_phys), intent(inout) :: chw(:,:) !(1:ncol,1:nlev) graupel number
real(kind_phys), intent(inout) :: vh (:,:) !(1:ncol,1:nlev) graupel volume

! Local variables: dimensions used in nssl_init
integer :: ims,ime, jms,jme, kms,kme, nx, nz, i,k
real :: nssl_params(20)
real(kind_phys) :: nssl_params(20)
integer :: ihailv,ipc
real(kind_phys), parameter :: qmin = 1.e-12
integer :: ierr
logical :: missing_vars = .False.


! Initialize the CCPP error handling variables
Expand Down Expand Up @@ -143,6 +165,19 @@ subroutine mp_nssl_init(ncol, nlev, errflg, errmsg, threads, restart, &

! For restart runs, the init is done here
if (restart) then

! For restart, check if the IC is from a different scheme that does not have all the needed variables
missing_vars = .False.
IF ( Any( qc > qmin .and. ccw == 0.0 ) ) missing_vars = .true.
IF ( .not. missing_vars .and. Any( qi > qmin .and. cci == 0.0 ) ) missing_vars = .true.
IF ( .not. missing_vars .and. Any( qs > qmin .and. csw == 0.0 ) ) missing_vars = .true.
IF ( .not. missing_vars .and. Any( qr > qmin .and. crw == 0.0 ) ) missing_vars = .true.
IF ( .not. missing_vars .and. Any( qh > qmin .and. (chw == 0.0 .or. vh == 0.0) ) ) missing_vars = .true.

#ifdef MPI
call MPI_Allreduce(missing_vars, missing_vars_global, 1, MPI_LOGICAL, MPI_LOR, mpicomm, ierr)
#endif

is_initialized = .true.
return
end if
Expand Down Expand Up @@ -312,13 +347,14 @@ subroutine mp_nssl_run(ncol, nlev, con_g, con_rd, mpirank, &
its,ite, jts,jte, kts,kte, i,j,k
integer :: itimestep ! timestep counter
integer :: ntmul, n
real, parameter :: dtpmax = 60. ! allow up to dt=75 (1.25*60)
real(kind_phys), parameter :: dtpmax = 60. ! allow up to dt=75 (1.25*60)
real(kind_phys) :: dtptmp
integer, parameter :: ndebug = 0
logical :: invertccn
real :: cwmas
real(kind_phys) :: cwmas

real(kind_phys), allocatable :: an(:,:,:,:) ! temporary scalar array



errflg = 0
Expand Down Expand Up @@ -529,8 +565,8 @@ subroutine mp_nssl_run(ncol, nlev, con_g, con_rd, mpirank, &
dtptmp = dtp
ntmul = 1
ENDIF
IF ( first_time_step .and. .not. restart ) THEN

IF ( first_time_step .and. ( .not. restart .or. missing_vars_global ) ) THEN
itimestep = 0 ! gets incremented to 1 in call loop
IF ( nssl_ccn_on ) THEN
IF ( invertccn ) THEN
Expand Down
95 changes: 95 additions & 0 deletions physics/MP/NSSL/mp_nssl.meta
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,101 @@
dimensions = ()
type = integer
intent = in
[mpicomm]
standard_name = mpi_communicator
long_name = MPI communicator
units = index
dimensions = ()
type = integer
intent = in
[qc]
standard_name = cloud_liquid_water_mixing_ratio
long_name = cloud water mixing ratio wrt dry+vapor (no condensates)
units = kg kg-1
dimensions = (horizontal_dimension ,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[qr]
standard_name = rain_mixing_ratio
long_name = rain water mixing ratio wrt dry+vapor (no condensates)
units = kg kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[qi]
standard_name = cloud_ice_mixing_ratio
long_name = ice water mixing ratio wrt dry+vapor (no condensates)
units = kg kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[qs]
standard_name = snow_mixing_ratio
long_name = snow water mixing ratio wrt dry+vapor (no condensates)
units = kg kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[qh]
standard_name = graupel_mixing_ratio
long_name = graupel mixing ratio wrt dry+vapor (no condensates)
units = kg kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[ccw]
standard_name = mass_number_concentration_of_cloud_liquid_water_particles_in_air
long_name = cloud droplet number concentration
units = kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[crw]
standard_name = mass_number_concentration_of_rain_water_in_air
long_name = rain number concentration
units = kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[cci]
standard_name = mass_number_concentration_of_cloud_ice_water_crystals_in_air
long_name = ice number concentration
units = kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[csw]
standard_name = mass_number_concentration_of_snow_in_air
long_name = snow number concentration
units = kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[chw]
standard_name = mass_number_concentration_of_graupel_in_air
long_name = graupel number concentration
units = kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[vh]
standard_name = graupel_volume
long_name = graupel particle volume
units = m3 kg-1
dimensions = (horizontal_dimension,vertical_layer_dimension)
type = real
kind = kind_phys
intent = inout
[con_g]
standard_name = gravitational_acceleration
long_name = gravitational acceleration
Expand Down

0 comments on commit 1545c6b

Please sign in to comment.