Skip to content

Commit

Permalink
Merge pull request ufs-community#71 from ufs-community/ufs/dev
Browse files Browse the repository at this point in the history
sync with the ufs/dev
  • Loading branch information
HelinWei-NOAA authored May 8, 2023
2 parents 7c750ea + eda81a5 commit 31c693b
Show file tree
Hide file tree
Showing 73 changed files with 21,114 additions and 4,100 deletions.
372 changes: 186 additions & 186 deletions CODEOWNERS

Large diffs are not rendered by default.

13 changes: 10 additions & 3 deletions physics/GFS_MP_generic_post.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,17 +29,17 @@ subroutine GFS_MP_generic_post_run(
graupelprv, draincprv, drainncprv, diceprv, dsnowprv, dgraupelprv, dtp, dfi_radar_max_intervals, &
dtend, dtidx, index_of_temperature, index_of_process_mp,ldiag3d, qdiag3d,dqdt_qmicro, lssav, num_dfi_radar, &
fh_dfi_radar,index_of_process_dfi_radar, ix_dfi_radar, dfi_radar_tten, radar_tten_limits, fhour, prevsq, &
errmsg, errflg)
iopt_lake, iopt_lake_clm, lkm, use_lake_model, errmsg, errflg)
!
use machine, only: kind_phys
use calpreciptype_mod, only: calpreciptype
implicit none

integer, intent(in) :: im, levs, kdt, nrcm, nncl, ntcw, ntrac, num_dfi_radar, index_of_process_dfi_radar
integer, intent(in) :: imp_physics, imp_physics_gfdl, imp_physics_thompson, imp_physics_mg, imp_physics_fer_hires
integer, intent(in) :: imp_physics_nssl
integer, intent(in) :: imp_physics_nssl, iopt_lake_clm, iopt_lake, lkm
logical, intent(in) :: cal_pre, lssav, ldiag3d, qdiag3d, cplflx, cplchm, cpllnd, progsigma, exticeden
integer, intent(in) :: index_of_temperature,index_of_process_mp
integer, intent(in) :: index_of_temperature,index_of_process_mp,use_lake_model(:)

integer :: dfi_radar_max_intervals
real(kind=kind_phys), intent(in) :: fh_dfi_radar(:), fhour
Expand Down Expand Up @@ -228,6 +228,13 @@ subroutine GFS_MP_generic_post_run(
dgraupelprv(:) = tem * graupelprv(:)
diceprv(:) = tem * iceprv(:)
end if
else if(lkm>0 .and. iopt_lake==iopt_lake_clm) then
do i=1,im
if(use_lake_model(i)>0) then
raincprv(i) = rainc(i)
rainncprv(i) = frain * rain1(i)
end if
end do
end if

if (cal_pre) then ! hchuang: add dominant precipitation type algorithm
Expand Down
28 changes: 28 additions & 0 deletions physics/GFS_MP_generic_post.meta
Original file line number Diff line number Diff line change
Expand Up @@ -832,6 +832,34 @@
dimensions = ()
type = logical
intent = in
[lkm]
standard_name = control_for_lake_model_execution_method
long_name = control for lake model execution: 0=no lake, 1=lake, 2=lake+nsst
units = flag
dimensions = ()
type = integer
intent = in
[iopt_lake]
standard_name = control_for_lake_model_selection
long_name = control for lake model selection
units = 1
dimensions = ()
type = integer
intent = in
[iopt_lake_clm]
standard_name = clm_lake_model_control_selection_value
long_name = value that indicates clm lake model in the control for lake model selection
units = 1
dimensions = ()
type = integer
intent = in
[use_lake_model]
standard_name = flag_for_using_lake_model
long_name = flag indicating lake points using a lake model
units = flag
dimensions = (horizontal_loop_extent)
type = integer
intent = in
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
19 changes: 13 additions & 6 deletions physics/GFS_debug.F90
Original file line number Diff line number Diff line change
Expand Up @@ -493,6 +493,8 @@ subroutine GFS_diagtoscreen_run (Model, Statein, Stateout, Sfcprop, Coupling,
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%oro_uf' , Sfcprop%oro_uf)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%hice' , Sfcprop%hice)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%weasd' , Sfcprop%weasd)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%weasdl' , Sfcprop%weasdl)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%%weasdi' , Sfcprop%weasdi)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%canopy' , Sfcprop%canopy)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%ffmm' , Sfcprop%ffmm)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%ffhh' , Sfcprop%ffhh)
Expand Down Expand Up @@ -613,7 +615,7 @@ subroutine GFS_diagtoscreen_run (Model, Statein, Stateout, Sfcprop, Coupling,
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Tbd%in_nm' , Tbd%in_nm)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Tbd%ccn_nm' , Tbd%ccn_nm)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Tbd%aer_nm' , Tbd%aer_nm)
if (Model%imfdeepcnv == Model%imfdeepcnv_gf) then
if (Model%imfdeepcnv == Model%imfdeepcnv_gf .or. Model%imfdeepcnv == Model%imfdeepcnv_unified) then
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Tbd%cactiv' , Tbd%cactiv)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Tbd%cactiv_m' , Tbd%cactiv_m)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Tbd%aod_gf' , Tbd%aod_gf)
Expand All @@ -624,6 +626,9 @@ subroutine GFS_diagtoscreen_run (Model, Statein, Stateout, Sfcprop, Coupling,
! call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%fluxr_n ', Diag%fluxr(:,n))
!end do
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%srunoff ', Diag%srunoff)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%evbs ', Diag%evbs)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%evcw ', Diag%evcw)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%sbsno ', Diag%sbsno)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%evbsa ', Diag%evbsa)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%evcwa ', Diag%evcwa)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%snohfa ', Diag%snohfa)
Expand Down Expand Up @@ -694,6 +699,7 @@ subroutine GFS_diagtoscreen_run (Model, Statein, Stateout, Sfcprop, Coupling,
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%tdomzr ', Diag%tdomzr)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%tdomip ', Diag%tdomip)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%tdoms ', Diag%tdoms)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Diag%trans ', Diag%trans)
! CCPP/RUC only
if (Model%lsm == Model%lsm_ruc) then
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Sfcprop%wetness ', Sfcprop%wetness)
Expand Down Expand Up @@ -1204,8 +1210,6 @@ subroutine GFS_interstitialtoscreen_run (Model, Statein, Stateout, Sfcprop, Coup
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%evap_ice ', Interstitial%evap_ice )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%evap_land ', Interstitial%evap_land )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%evap_water ', Interstitial%evap_water )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%evbs ', Interstitial%evbs )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%evcw ', Interstitial%evcw )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%ext_diag_thompson_reset', Interstitial%ext_diag_thompson_reset)
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%faerlw ', Interstitial%faerlw )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%faersw ', Interstitial%faersw )
Expand Down Expand Up @@ -1285,7 +1289,7 @@ subroutine GFS_interstitialtoscreen_run (Model, Statein, Stateout, Sfcprop, Coup
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%qss_ice ', Interstitial%qss_ice )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%qss_land ', Interstitial%qss_land )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%qss_water ', Interstitial%qss_water )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%fullradar_diag ', Interstitial%fullradar_diag )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%radar_reset ', Interstitial%radar_reset )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%raddt ', Interstitial%raddt )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%raincd ', Interstitial%raincd )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%raincs ', Interstitial%raincs )
Expand All @@ -1302,7 +1306,6 @@ subroutine GFS_interstitialtoscreen_run (Model, Statein, Stateout, Sfcprop, Coup
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%save_tcp ', Interstitial%save_tcp )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%save_u ', Interstitial%save_u )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%save_v ', Interstitial%save_v )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%sbsno ', Interstitial%sbsno )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%scmpsw%uvbfc ', Interstitial%scmpsw%uvbfc )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%scmpsw%uvbf0 ', Interstitial%scmpsw%uvbf0 )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%scmpsw%nirbm ', Interstitial%scmpsw%nirbm )
Expand All @@ -1315,6 +1318,8 @@ subroutine GFS_interstitialtoscreen_run (Model, Statein, Stateout, Sfcprop, Coup
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%sigmafrac ', Interstitial%sigmafrac )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%sigmatot ', Interstitial%sigmatot )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%snowc ', Interstitial%snowc )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%snowd_ice ', Interstitial%snowd_ice )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%snowd_land ', Interstitial%snowd_land )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%snohf ', Interstitial%snohf )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%snowmt ', Interstitial%snowmt )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%stress ', Interstitial%stress )
Expand All @@ -1327,7 +1332,6 @@ subroutine GFS_interstitialtoscreen_run (Model, Statein, Stateout, Sfcprop, Coup
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%tprcp_ice ', Interstitial%tprcp_ice )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%tprcp_land ', Interstitial%tprcp_land )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%tprcp_water ', Interstitial%tprcp_water )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%trans ', Interstitial%trans )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%tseal ', Interstitial%tseal )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%tsfa ', Interstitial%tsfa )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%tsfc_water ', Interstitial%tsfc_water )
Expand All @@ -1341,6 +1345,9 @@ subroutine GFS_interstitialtoscreen_run (Model, Statein, Stateout, Sfcprop, Coup
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%vdftra ', Interstitial%vdftra )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%vegf1d ', Interstitial%vegf1d )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%wcbmax ', Interstitial%wcbmax )
! call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%weasd_ice ', Interstitial%weasd_ice )
! call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%weasd_land ', Interstitial%weasd_land )
! call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%weasd_water ', Interstitial%weasd_water )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%wind ', Interstitial%wind )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%work1 ', Interstitial%work1 )
call print_var(mpirank, omprank, blkno, Grid%xlat_d, Grid%xlon_d, 'Interstitial%work2 ', Interstitial%work2 )
Expand Down
32 changes: 29 additions & 3 deletions physics/GFS_phys_time_vary.fv3.F90
Original file line number Diff line number Diff line change
Expand Up @@ -80,17 +80,22 @@ subroutine GFS_phys_time_vary_init (
zwtxy, xlaixy, xsaixy, lfmassxy, stmassxy, rtmassxy, woodxy, stblcpxy, fastcpxy, &
smcwtdxy, deeprechxy, rechxy, snowxy, snicexy, snliqxy, tsnoxy , smoiseq, zsnsoxy, &
slc, smc, stc, tsfcl, snowd, canopy, tg3, stype, con_t0c, lsm_cold_start, nthrds, &
errmsg, errflg)
lkm, use_lake_model, lakefrac, lakedepth, iopt_lake, iopt_lake_clm, iopt_lake_flake, &
lakefrac_threshold, lakedepth_threshold, errmsg, errflg)

implicit none

! Interface variables
integer, intent(in) :: me, master, ntoz, iccn, iflip, im, nx, ny, levs, iaermdl
logical, intent(in) :: h2o_phys, iaerclm, lsm_cold_start
integer, intent(in) :: idate(:)
real(kind_phys), intent(in) :: fhour
integer, intent(in) :: idate(:), iopt_lake, iopt_lake_clm, iopt_lake_flake
real(kind_phys), intent(in) :: fhour, lakefrac_threshold, lakedepth_threshold
real(kind_phys), intent(in) :: xlat_d(:), xlon_d(:)

integer, intent(in) :: lkm
integer, intent(inout) :: use_lake_model(:)
real(kind=kind_phys), intent(in ) :: lakefrac(:), lakedepth(:)

integer, intent(inout) :: jindx1_o3(:), jindx2_o3(:), jindx1_h(:), jindx2_h(:)
real(kind_phys), intent(inout) :: ddy_o3(:), ddy_h(:)
real(kind_phys), intent(in) :: ozpl(:,:,:), h2opl(:,:,:)
Expand Down Expand Up @@ -670,6 +675,27 @@ subroutine GFS_phys_time_vary_init (
endif noahmp_init
endif lsm_init

!Lake model
if(lkm>0 .and. iopt_lake>0) then
! A lake model is enabled.
do i = 1, im
!if (lakefrac(i) > 0.0 .and. lakedepth(i) > 1.0 ) then

! The lake data must say there's a lake here (lakefrac) with a depth (lakedepth)
if (lakefrac(i) > lakefrac_threshold .and. lakedepth(i) > lakedepth_threshold ) then
! This is a lake point. Inform the other schemes to use a lake model, and possibly nsst (lkm)
use_lake_model(i) = lkm
cycle
else
! Not a valid lake point.
use_lake_model(i) = 0
endif
enddo
else
! Lake model is disabled or settings are invalid.
use_lake_model = 0
endif

is_initialized = .true.

contains
Expand Down
67 changes: 67 additions & 0 deletions physics/GFS_phys_time_vary.fv3.meta
Original file line number Diff line number Diff line change
Expand Up @@ -902,6 +902,73 @@
dimensions = ()
type = integer
intent = in
[lkm]
standard_name = control_for_lake_model_execution_method
long_name = control for lake model execution: 0=no lake, 1=lake, 2=lake+nsst
units = flag
dimensions = ()
type = integer
intent = in
[use_lake_model]
standard_name = flag_for_using_lake_model
long_name = flag indicating lake points using a lake model
units = flag
dimensions = (horizontal_dimension)
type = integer
intent = inout
[lakefrac]
standard_name = lake_area_fraction
long_name = fraction of horizontal grid area occupied by lake
units = frac
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
[lakedepth]
standard_name = lake_depth
long_name = lake depth
units = m
dimensions = (horizontal_dimension)
type = real
kind = kind_phys
intent = in
[iopt_lake]
standard_name = control_for_lake_model_selection
long_name = control for lake model selection
units = 1
dimensions = ()
type = integer
intent = in
[iopt_lake_clm]
standard_name = clm_lake_model_control_selection_value
long_name = value that indicates clm lake model in the control for lake model selection
units = 1
dimensions = ()
type = integer
intent = in
[iopt_lake_flake]
standard_name = flake_model_control_selection_value
long_name = value that indicates flake model in the control for lake model selection
units = 1
dimensions = ()
type = integer
intent = in
[lakefrac_threshold]
standard_name = lakefrac_threshold_for_enabling_lake_model
long_name = fraction of horizontal grid area occupied by lake must be greater than this value to enable a lake model
units = frac
dimensions = ()
type = real
kind = kind_phys
intent = in
[lakedepth_threshold]
standard_name = lake_depth_threshold_for_enabling_lake_model
long_name = lake depth must be greater than this value to enable a lake model
units = m
dimensions = ()
type = real
kind = kind_phys
intent = in
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
Loading

0 comments on commit 31c693b

Please sign in to comment.