Skip to content

Commit

Permalink
Merge pull request #87 from dustinswales/ufs-dev-PR30a
Browse files Browse the repository at this point in the history
ufs-dev-PR30a
  • Loading branch information
dustinswales authored Mar 17, 2023
2 parents 1c27fe8 + ab23e91 commit 782d6dc
Show file tree
Hide file tree
Showing 24 changed files with 650 additions and 147 deletions.
2 changes: 1 addition & 1 deletion atmos_cubed_sphere
16 changes: 7 additions & 9 deletions atmos_model.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1477,6 +1477,10 @@ subroutine update_atmos_chemistry(state, rc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, file=__FILE__, rcToReturn=rc)) return

call cplFieldGet(state,'inst_pres_interface', farrayPtr3d=prsi, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, file=__FILE__, rcToReturn=rc)) return

if (GFS_Control%cplaqm) then

call cplFieldGet(state,'canopy_moisture_storage', farrayPtr2d=canopy, rc=localrc)
Expand Down Expand Up @@ -1541,10 +1545,6 @@ subroutine update_atmos_chemistry(state, rc)

else

call cplFieldGet(state,'inst_pres_interface', farrayPtr3d=prsi, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, &
line=__LINE__, file=__FILE__, rcToReturn=rc)) return

call cplFieldGet(state,'inst_liq_nonconv_tendency_levels', &
farrayPtr3d=pflls, rc=localrc)
if (ESMF_LogFoundError(rcToCheck=localrc, msg=ESMF_LOGERR_PASSTHRU, &
Expand Down Expand Up @@ -1592,6 +1592,7 @@ subroutine update_atmos_chemistry(state, rc)
ix = Atm_block%ixp(ib,jb)
!--- interface values
phii(i,j,k) = GFS_data(nb)%Statein%phii(ix,k)
prsi(i,j,k) = GFS_data(nb)%Statein%prsi(ix,k)
!--- layer values
prsl(i,j,k) = GFS_Data(nb)%Statein%prsl(ix,k)
phil(i,j,k) = GFS_Data(nb)%Statein%phil(ix,k)
Expand All @@ -1600,8 +1601,6 @@ subroutine update_atmos_chemistry(state, rc)
va (i,j,k) = GFS_Data(nb)%Stateout%gv0(ix,k)
cldfra(i,j,k) = GFS_Data(nb)%IntDiag%cldfra(ix,k)
if (.not.GFS_Control%cplaqm) then
!--- interface values
prsi(i,j,k) = GFS_data(nb)%Statein%prsi(ix,k)
!--- layer values
pfils (i,j,k) = GFS_Data(nb)%Coupling%pfi_lsan(ix,k)
pflls (i,j,k) = GFS_Data(nb)%Coupling%pfl_lsan(ix,k)
Expand All @@ -1620,8 +1619,7 @@ subroutine update_atmos_chemistry(state, rc)
nb = Atm_block%blkno(ib,jb)
ix = Atm_block%ixp(ib,jb)
phii(i,j,k) = GFS_data(nb)%Statein%phii(ix,k)
if (.not.GFS_Control%cplaqm) &
prsi(i,j,k) = GFS_data(nb)%Statein%prsi(ix,k)
prsi(i,j,k) = GFS_data(nb)%Statein%prsi(ix,k)
enddo
enddo

Expand Down Expand Up @@ -1728,6 +1726,7 @@ subroutine update_atmos_chemistry(state, rc)

if (GFS_control%debug) then
! -- diagnostics
write(6,'("update_atmos: prsi - min/max/avg",3g16.6)') minval(prsi), maxval(prsi), sum(prsi)/size(prsi)
write(6,'("update_atmos: phii - min/max/avg",3g16.6)') minval(phii), maxval(phii), sum(phii)/size(phii)
write(6,'("update_atmos: prsl - min/max/avg",3g16.6)') minval(prsl), maxval(prsl), sum(prsl)/size(prsl)
write(6,'("update_atmos: phil - min/max/avg",3g16.6)') minval(phil), maxval(phil), sum(phil)/size(phil)
Expand Down Expand Up @@ -1766,7 +1765,6 @@ subroutine update_atmos_chemistry(state, rc)
write(6,'("update_atmos: xlai - min/max/avg",3g16.6)') minval(xlai), maxval(xlai), sum(xlai)/size(xlai)
write(6,'("update_atmos: stype - min/max/avg",3g16.6)') minval(stype), maxval(stype), sum(stype)/size(stype)
else
write(6,'("update_atmos: prsi - min/max/avg",3g16.6)') minval(prsi), maxval(prsi), sum(prsi)/size(prsi)
write(6,'("update_atmos: flake - min/max/avg",3g16.6)') minval(flake), maxval(flake), sum(flake)/size(flake)
write(6,'("update_atmos: focn - min/max/avg",3g16.6)') minval(focn), maxval(focn), sum(focn)/size(focn)
write(6,'("update_atmos: shfsfc - min/max/avg",3g16.6)') minval(shfsfc), maxval(shfsfc), sum(shfsfc)/size(shfsfc)
Expand Down
10 changes: 5 additions & 5 deletions ccpp/data/CCPP_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -249,7 +249,7 @@ module CCPP_typedefs
real (kind=kind_phys), pointer :: qss_ice(:) => null() !<
real (kind=kind_phys), pointer :: qss_land(:) => null() !<
real (kind=kind_phys), pointer :: qss_water(:) => null() !<
logical :: radar_reset !<
logical :: fullradar_diag !<
real (kind=kind_phys) :: raddt !<
real (kind=kind_phys), pointer :: rainmp(:) => null() !<
real (kind=kind_phys), pointer :: raincd(:) => null() !<
Expand Down Expand Up @@ -1478,11 +1478,11 @@ subroutine gfs_interstitial_phys_reset (Interstitial, Model)
! Use same logic in UFS to reset Thompson extended diagnostics
Interstitial%ext_diag_thompson_reset = Interstitial%max_hourly_reset
!
! Set flag for resetting radar reflectivity calculation
if (Model%nsradar_reset<0) then
Interstitial%radar_reset = .true.
! Frequency flag for computing the full radar reflectivity (water coated ice)
if (Model%nsfullradar_diag<0) then
Interstitial%fullradar_diag = .true.
else
Interstitial%radar_reset = mod(Model%kdt-1, nint(Model%nsradar_reset/Model%dtp)) == 0
Interstitial%fullradar_diag = (Model%kdt == 1 .or. mod(Model%kdt, nint(Model%nsfullradar_diag/Model%dtp)) == 0)
end if
!
end subroutine gfs_interstitial_phys_reset
Expand Down
6 changes: 3 additions & 3 deletions ccpp/data/CCPP_typedefs.meta
Original file line number Diff line number Diff line change
Expand Up @@ -1699,9 +1699,9 @@
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
[radar_reset]
standard_name = flag_for_resetting_radar_reflectivity_calculation
long_name = flag for resetting radar reflectivity calculation
[fullradar_diag]
standard_name = do_full_radar_reflectivity
long_name = flag for computing full radar reflectivity
units = flag
dimensions = ()
type = logical
Expand Down
62 changes: 49 additions & 13 deletions ccpp/data/GFS_typedefs.F90
Original file line number Diff line number Diff line change
Expand Up @@ -372,7 +372,6 @@ module GFS_typedefs
real (kind=kind_phys), pointer :: clw_surf_ice(:) => null() !< RUC LSM: moist cloud water mixing ratio at surface over ice
real (kind=kind_phys), pointer :: qwv_surf_land(:) => null() !< RUC LSM: water vapor mixing ratio at surface over land
real (kind=kind_phys), pointer :: qwv_surf_ice(:) => null() !< RUC LSM: water vapor mixing ratio at surface over ice
real (kind=kind_phys), pointer :: rhofr(:) => null() !< RUC LSM: density of frozen precipitation
real (kind=kind_phys), pointer :: tsnow_land(:) => null() !< RUC LSM: snow temperature at the bottom of the first snow layer over land
real (kind=kind_phys), pointer :: tsnow_ice(:) => null() !< RUC LSM: snow temperature at the bottom of the first snow layer over ice
real (kind=kind_phys), pointer :: snowfallac_land(:) => null() !< ruc lsm diagnostics over land
Expand Down Expand Up @@ -920,7 +919,7 @@ module GFS_typedefs
logical :: ltaerosol !< flag for aerosol version
logical :: mraerosol !< flag for merra2_aerosol_aware
logical :: lradar !< flag for radar reflectivity
real(kind=kind_phys) :: nsradar_reset !< seconds between resetting radar reflectivity calculation
real(kind=kind_phys) :: nsfullradar_diag!< seconds between resetting radar reflectivity calculation
real(kind=kind_phys) :: ttendlim !< temperature tendency limiter per time step in K/s
logical :: ext_diag_thompson !< flag for extended diagnostic output from Thompson
integer :: thompson_ext_ndiag3d=37 !< number of 3d arrays for extended diagnostic output from Thompson
Expand Down Expand Up @@ -954,6 +953,7 @@ module GFS_typedefs
integer :: lsnow_lsm !< maximum number of snow layers internal to land surface model
integer :: lsnow_lsm_lbound!< lower bound for snow arrays, depending on lsnow_lsm
integer :: lsnow_lsm_ubound!< upper bound for snow arrays, depending on lsnow_lsm
logical :: exticeden !< flag for calculating frozen precip ice density outside of the LSM
real(kind=kind_phys), pointer :: zs(:) => null() !< depth of soil levels for land surface model
real(kind=kind_phys), pointer :: dzs(:) => null() !< thickness of soil levels for land surface model
real(kind=kind_phys), pointer :: pores(:) => null() !< max soil moisture for a given soil type for land surface model
Expand Down Expand Up @@ -1758,6 +1758,14 @@ module GFS_typedefs
real (kind=kind_phys), pointer :: toticeb(:) => null() !< accumulated ice precipitation in bucket (kg/m2)
real (kind=kind_phys), pointer :: totsnwb(:) => null() !< accumulated snow precipitation in bucket (kg/m2)
real (kind=kind_phys), pointer :: totgrpb(:) => null() !< accumulated graupel precipitation in bucket (kg/m2)
real (kind=kind_phys), pointer :: frzr (:) => null() !< accumulated surface freezing rain (m)
real (kind=kind_phys), pointer :: frzrb (:) => null() !< accumulated surface freezing rain in bucket (m)
real (kind=kind_phys), pointer :: frozr (:) => null() !< accumulated surface graupel (m)
real (kind=kind_phys), pointer :: frozrb (:) => null() !< accumulated surface graupel in bucket (m)
real (kind=kind_phys), pointer :: tsnowp (:) => null() !< accumulated surface snowfall (m)
real (kind=kind_phys), pointer :: tsnowpb(:) => null() !< accumulated surface snowfall in bucket (m)
real (kind=kind_phys), pointer :: rhonewsn1(:) => null() !< precipitation ice density outside RUC LSM (kg/m3)
real (kind=kind_phys), pointer :: rhosnf(:) => null() !< precipitation ice density inside RUC LSM (kg/m3)

!--- MYNN variables
real (kind=kind_phys), pointer :: edmf_a (:,:) => null() !
Expand Down Expand Up @@ -2449,7 +2457,6 @@ subroutine sfcprop_create (Sfcprop, IM, Model)
allocate (Sfcprop%clw_surf_ice (IM))
allocate (Sfcprop%qwv_surf_land (IM))
allocate (Sfcprop%qwv_surf_ice (IM))
allocate (Sfcprop%rhofr (IM))
allocate (Sfcprop%tsnow_land (IM))
allocate (Sfcprop%tsnow_ice (IM))
allocate (Sfcprop%snowfallac_land (IM))
Expand All @@ -2465,7 +2472,6 @@ subroutine sfcprop_create (Sfcprop, IM, Model)
Sfcprop%qwv_surf_land = clear_val
Sfcprop%qwv_surf_ice = clear_val
Sfcprop%flag_frsoil = clear_val
Sfcprop%rhofr = clear_val
Sfcprop%tsnow_land = clear_val
Sfcprop%tsnow_ice = clear_val
Sfcprop%snowfallac_land = clear_val
Expand Down Expand Up @@ -3164,7 +3170,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
logical :: ltaerosol = .false. !< flag for aerosol version
logical :: mraerosol = .false. !< flag for merra2_aerosol_aware
logical :: lradar = .false. !< flag for radar reflectivity
real(kind=kind_phys) :: nsradar_reset = -999.0 !< seconds between resetting radar reflectivity calculation, set to <0 for every time step
real(kind=kind_phys) :: nsfullradar_diag = -999.0 !< seconds between resetting radar reflectivity calculation, set to <0 for every time step
real(kind=kind_phys) :: ttendlim = -999.0 !< temperature tendency limiter, set to <0 to deactivate
logical :: ext_diag_thompson = .false. !< flag for extended diagnostic output from Thompson
real(kind=kind_phys) :: dt_inner = -999.0 !< time step for the inner loop
Expand All @@ -3182,6 +3188,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
integer :: lsoil = 4 !< number of soil layers
integer :: lsoil_lsm = -1 !< number of soil layers internal to land surface model; -1 use lsoil
integer :: lsnow_lsm = 3 !< maximum number of snow layers internal to land surface model
logical :: exticeden = .false. !< Use variable precip ice density for NOAH LSM if true or original formulation
logical :: rdlai = .false. !< read LAI from input file (for RUC LSM or NOAH LSM WRFv4)
logical :: ua_phys = .false. !< flag for using University of Arizona? extension to NOAH LSM WRFv4
logical :: usemonalb = .true. !< flag to read surface diffused shortwave albedo from input file for NOAH LSM WRFv4
Expand Down Expand Up @@ -3576,7 +3583,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
mg_do_graupel, mg_do_hail, mg_nccons, mg_nicons, mg_ngcons, &
mg_ncnst, mg_ninst, mg_ngnst, sed_supersat, do_sb_physics, &
mg_alf, mg_qcmin, mg_do_ice_gmao, mg_do_liq_liu, &
ltaerosol, lradar, nsradar_reset, lrefres, ttendlim, &
ltaerosol, lradar, nsfullradar_diag, lrefres, ttendlim, &
ext_diag_thompson, dt_inner, lgfdlmprad, &
sedi_semi, decfl, &
nssl_cccn, nssl_alphah, nssl_alphahl, &
Expand All @@ -3586,7 +3593,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
!--- land/surface model control
lsm, lsoil, lsoil_lsm, lsnow_lsm, kice, rdlai, &
nmtvr, ivegsrc, use_ufo, iopt_thcnd, ua_phys, usemonalb, &
aoasis, fasdas, &
aoasis, fasdas,exticeden, &
! Noah MP options
iopt_dveg,iopt_crs,iopt_btr,iopt_run,iopt_sfc, iopt_frz, &
iopt_inf, iopt_rad,iopt_alb,iopt_snf,iopt_tbot,iopt_stc, &
Expand Down Expand Up @@ -4166,7 +4173,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
stop
end if
Model%lradar = lradar
Model%nsradar_reset = nsradar_reset
Model%nsfullradar_diag = nsfullradar_diag
Model%ttendlim = ttendlim
Model%ext_diag_thompson= ext_diag_thompson
if (dt_inner>0) then
Expand Down Expand Up @@ -4274,7 +4281,15 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%ivegsrc = ivegsrc
Model%isot = isot
Model%use_ufo = use_ufo

Model%exticeden = exticeden
if (Model%exticeden .and. &
(Model%imp_physics /= Model%imp_physics_gfdl .and. Model%imp_physics /= Model%imp_physics_thompson .and. &
Model%imp_physics /= Model%imp_physics_nssl )) then
!see GFS_MP_generic_post.F90; exticeden is only compatible with GFDL,
!Thompson, or NSSL MP
print *,' Using exticeden = T is only valid when using GFDL, Thompson, or NSSL microphysics.'
stop
end if
! GFDL surface layer options
Model%lcurr_sf = lcurr_sf
Model%pert_cd = pert_cd
Expand All @@ -4295,7 +4310,11 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
Model%iopt_inf = iopt_inf
Model%iopt_rad = iopt_rad
Model%iopt_alb = iopt_alb
Model%iopt_snf = iopt_snf
if (Model%lsm==Model%lsm_noahmp .and. Model%exticeden .and. iopt_snf == 4) then
Model%iopt_snf = 5
else
Model%iopt_snf = iopt_snf
end if
Model%iopt_tbot = iopt_tbot
Model%iopt_stc = iopt_stc
Model%iopt_trs = iopt_trs
Expand Down Expand Up @@ -5175,6 +5194,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
if (Model%me == Model%master) then
if (Model%lsm == 1) then
print *,' NOAH Land Surface Model used'

elseif (Model%lsm == 0) then
print *,' OSU no longer supported - job aborted'
stop
Expand Down Expand Up @@ -5471,7 +5491,7 @@ subroutine control_initialize (Model, nlunit, fn_nml, me, master, &
' decfl=',decfl, &
' effr_in =',Model%effr_in, &
' lradar =',Model%lradar, &
' nsradar_reset =',Model%nsradar_reset, &
' nsfullradar_diag =',Model%nsfullradar_diag, &
' num_p3d =',Model%num_p3d, &
' num_p2d =',Model%num_p2d

Expand Down Expand Up @@ -5985,7 +6005,7 @@ subroutine control_print(Model)
print *, ' ltaerosol : ', Model%ltaerosol
print *, ' mraerosol : ', Model%mraerosol
print *, ' lradar : ', Model%lradar
print *, ' nsradar_reset : ', Model%nsradar_reset
print *, ' nsfullradar_diag : ', Model%nsfullradar_diag
print *, ' lrefres : ', Model%lrefres
print *, ' ttendlim : ', Model%ttendlim
print *, ' ext_diag_thompson : ', Model%ext_diag_thompson
Expand Down Expand Up @@ -7009,6 +7029,14 @@ subroutine diag_create (Diag, IM, Model)
allocate (Diag%epi (IM))
allocate (Diag%smcwlt2 (IM))
allocate (Diag%smcref2 (IM))
allocate (Diag%rhonewsn1 (IM))
allocate (Diag%rhosnf (IM))
allocate (Diag%frzr (IM))
allocate (Diag%frzrb (IM))
allocate (Diag%frozr (IM))
allocate (Diag%frozrb (IM))
allocate (Diag%tsnowp (IM))
allocate (Diag%tsnowpb (IM))
if (.not. Model%lsm == Model%lsm_ruc) then
allocate (Diag%wet1 (IM))
end if
Expand Down Expand Up @@ -7344,6 +7372,9 @@ subroutine diag_phys_zero (Diag, Model, linit, iauwindow_center)
Diag%toticeb = zero
Diag%totsnwb = zero
Diag%totgrpb = zero
Diag%frzrb = zero
Diag%frozrb = zero
Diag%tsnowpb = zero

!--- MYNN variables:
if (Model%do_mynnedmf) then
Expand Down Expand Up @@ -7464,7 +7495,9 @@ subroutine diag_phys_zero (Diag, Model, linit, iauwindow_center)
Diag%t02min = 999.
Diag%rh02max = -999.
Diag%rh02min = 999.
Diag%pratemax = 0.
Diag%pratemax = 0.
Diag%rhonewsn1 = 200.
Diag%rhosnf = -1.e3
set_totprcp = .false.
if (present(linit) ) set_totprcp = linit
if (present(iauwindow_center) ) set_totprcp = iauwindow_center
Expand All @@ -7474,6 +7507,9 @@ subroutine diag_phys_zero (Diag, Model, linit, iauwindow_center)
Diag%totice = zero
Diag%totsnw = zero
Diag%totgrp = zero
Diag%frzr = zero
Diag%frozr = zero
Diag%tsnowp = zero
endif

end subroutine diag_phys_zero
Expand Down
Loading

0 comments on commit 782d6dc

Please sign in to comment.