Skip to content

Commit

Permalink
Merge upstream@4ac3009 into feature/ufs_fire_cpl
Browse files Browse the repository at this point in the history
  • Loading branch information
danrosen25 committed Feb 29, 2024
2 parents eb9b329 + 4ac3009 commit e399c22
Show file tree
Hide file tree
Showing 46 changed files with 1,267 additions and 466 deletions.
5 changes: 1 addition & 4 deletions .gitmodules
Original file line number Diff line number Diff line change
@@ -1,7 +1,4 @@
[submodule "physics/rte-rrtmgp"]
[submodule "physics/Radiation/RRTMGP/rte-rrtmgp"]
path = physics/Radiation/RRTMGP/rte-rrtmgp
url = https://github.com/earth-system-radiation/rte-rrtmgp
branch = main
[submodule "physics/Radiation/RRTMGP/rte-rrtmgp"]
path = physics/Radiation/RRTMGP/rte-rrtmgp
url = https://github.com/earth-system-radiation/rte-rrtmgp
2 changes: 2 additions & 0 deletions CODEOWNERS
Validating CODEOWNERS rules …
Original file line number Diff line number Diff line change
Expand Up @@ -196,6 +196,8 @@ physics/ysuvdif.* @Qingfu-Liu @WeiguoWang-NOAA
physics/zhaocarr_gscond.* @RuiyuSun @grantfirl @Qingfu-Liu @dustinswales
physics/zhaocarr_precpd.* @RuiyuSun @grantfirl @Qingfu-Liu @dustinswales

physics/sfc_land.* @uturuncoglu @barlage

########################################################################

# Lines starting with '#' are comments.
Expand Down
5 changes: 3 additions & 2 deletions physics/CONV/Grell_Freitas/cu_gf_deep.F90
Original file line number Diff line number Diff line change
Expand Up @@ -142,13 +142,13 @@ subroutine cu_gf_deep_run( &
!! betwee -1 and +1
,do_capsuppress,cap_suppress_j & !
,k22 & !
,jmin,tropics) !
,jmin,kdt,tropics) !

implicit none

integer &
,intent (in ) :: &
nranflag,itf,ktf,its,ite, kts,kte,ipr,imid
nranflag,itf,ktf,its,ite, kts,kte,ipr,imid,kdt
integer, intent (in ) :: &
ichoice,nchem
real(kind=kind_phys), dimension (its:ite,4) &
Expand Down Expand Up @@ -591,6 +591,7 @@ subroutine cu_gf_deep_run( &
sig(i)=(1.-frh)**2
!frh_out(i) = frh
if(forcing(i,7).eq.0.)sig(i)=1.
if(kdt.le.(3600./dtime))sig(i)=1.
frh_out(i) = frh*sig(i)
enddo
!$acc end kernels
Expand Down
8 changes: 4 additions & 4 deletions physics/CONV/Grell_Freitas/cu_gf_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ subroutine cu_gf_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
dfi_radar_max_intervals,ldiag3d,qci_conv,do_cap_suppress, &
maxupmf,maxMF,do_mynnedmf,ichoice_in,ichoicem_in,ichoice_s_in, &
spp_cu_deep,spp_wts_cu_deep,nchem,chem3d,fscav,wetdpc_deep, &
do_smoke_transport,errmsg,errflg)
do_smoke_transport,kdt,errmsg,errflg)
!-------------------------------------------------------------
implicit none
integer, parameter :: maxiens=1
Expand All @@ -95,7 +95,7 @@ subroutine cu_gf_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
integer :: ishallow_g3 ! depend on imfshalcnv
!-------------------------------------------------------------
integer :: its,ite, jts,jte, kts,kte
integer, intent(in ) :: im,km,ntracer, nchem
integer, intent(in ) :: im,km,ntracer,nchem,kdt
integer, intent(in ) :: ichoice_in,ichoicem_in,ichoice_s_in
logical, intent(in ) :: flag_init, flag_restart, do_mynnedmf
logical, intent(in ) :: flag_for_scnv_generic_tend,flag_for_dcnv_generic_tend
Expand Down Expand Up @@ -766,7 +766,7 @@ subroutine cu_gf_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
! betwee -1 and +1
,do_cap_suppress_here,cap_suppress_j &
,k22m &
,jminm,tropics)
,jminm,kdt,tropics)
!$acc kernels
do i=its,itf
do k=kts,ktf
Expand Down Expand Up @@ -853,7 +853,7 @@ subroutine cu_gf_driver_run(ntracer,garea,im,km,dt,flag_init,flag_restart,&
! betwee -1 and +1
,do_cap_suppress_here,cap_suppress_j &
,k22 &
,jmin,tropics)
,jmin,kdt,tropics)
jpr=0
ipr=0
!$acc kernels
Expand Down
7 changes: 7 additions & 0 deletions physics/CONV/Grell_Freitas/cu_gf_driver.meta
Original file line number Diff line number Diff line change
Expand Up @@ -651,6 +651,13 @@
type = real
kind = kind_phys
intent = inout
[kdt]
standard_name = index_of_timestep
long_name = current forecast iteration
units = index
dimensions = ()
type = integer
intent = in
[errmsg]
standard_name = ccpp_error_message
long_name = error message for error handling in CCPP
Expand Down
2 changes: 1 addition & 1 deletion physics/CONV/SAMF/samfshalcnv.f
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ subroutine samfshalcnv_run(im,km,itc,ntc,cliq,cp,cvap, &
parameter(cinacrmx=-120.,shevf=2.0)
parameter(dtmax=10800.,dtmin=600.)
parameter(bb1=4.0,bb2=0.8,csmf=0.2)
parameter(tkcrt=2.,cmxfac=15.)
parameter(tkcrt=2.,cmxfac=10.)
! parameter(bet1=1.875,cd1=.506,f1=2.0,gam1=.5)
parameter(betaw=.03,dxcrtc0=9.e3)
parameter(h1=0.33333333)
Expand Down
4 changes: 2 additions & 2 deletions physics/GWD/unified_ugwp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -253,7 +253,7 @@ subroutine unified_ugwp_run(me, master, im, levs, ak,bk, ntrac, dtp, fhzero, kdt
cdmbgwd, jdat, xlat, xlat_d, sinlat, coslat, area, &
ugrs, vgrs, tgrs, q1, prsi, prsl, prslk, phii, phil, &
del, kpbl, dusfcg, dvsfcg, gw_dudt, gw_dvdt, gw_dtdt, gw_kdis, &
tau_tofd, tau_mtb, tau_ogw, tau_ngw, zmtb, zlwb, zogw, &
tau_tofd, tau_mtb, tau_ogw, tau_ngw, &
dudt_mtb, dudt_tms, du3dt_mtb, du3dt_ogw, du3dt_tms, &
dudt, dvdt, dtdt, rdxzb, con_g, con_omega, con_pi, con_cp, con_rd, con_rv, &
con_rerth, con_fvirt, rain, ntke, q_tke, dqdt_tke, lprnt, ipr, &
Expand Down Expand Up @@ -309,7 +309,7 @@ subroutine unified_ugwp_run(me, master, im, levs, ak,bk, ntrac, dtp, fhzero, kdt
& slmsk(:)

real(kind=kind_phys), intent(out), dimension(:) :: dusfcg, dvsfcg
real(kind=kind_phys), intent(out), dimension(:) :: zmtb, zlwb, zogw, rdxzb
real(kind=kind_phys), intent(out), dimension(:) :: rdxzb
real(kind=kind_phys), intent(out), dimension(:) :: tau_mtb, tau_ogw, tau_tofd, tau_ngw
real(kind=kind_phys), intent(out), dimension(:,:) :: gw_dudt, gw_dvdt, gw_dtdt, gw_kdis
real(kind=kind_phys), intent(out), dimension(:,:) :: dudt_mtb, dudt_tms
Expand Down
24 changes: 0 additions & 24 deletions physics/GWD/unified_ugwp.meta
Original file line number Diff line number Diff line change
Expand Up @@ -900,30 +900,6 @@
type = real
kind = kind_phys
intent = out
[zmtb]
standard_name = height_of_mountain_blocking
long_name = height of mountain blocking drag
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[zlwb]
standard_name = height_of_low_level_wave_breaking
long_name = height of low level wave breaking
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[zogw]
standard_name = height_of_launch_level_of_orographic_gravity_wave
long_name = height of launch level of orographic gravity wave
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[dudt_mtb]
standard_name = instantaneous_change_in_x_wind_due_to_mountain_blocking_drag
long_name = instantaneous change in x wind due to mountain blocking drag
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ module GFS_suite_stateout_update
subroutine GFS_suite_stateout_update_run (im, levs, ntrac, dtp, tgrs, ugrs, vgrs, qgrs, &
dudt, dvdt, dtdt, dqdt, gt0, gu0, gv0, gq0, oz0, ntiw, nqrimef, imp_physics, &
imp_physics_fer_hires, epsq, ozphys, oz_phys_2015, oz_phys_2006, con_1ovg, prsl, &
dp, ozpl, do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz, errmsg, errflg)
dp, ozpl, qdiag3d, do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz, errmsg, errflg)

! Inputs
integer, intent(in ) :: im
Expand All @@ -31,12 +31,13 @@ subroutine GFS_suite_stateout_update_run (im, levs, ntrac, dtp, tgrs, ugrs, vgrs
real(kind=kind_phys), intent(in ), dimension(:,:,:) :: qgrs, ozpl
real(kind=kind_phys), intent(in ), dimension(:,:) :: dudt, dvdt, dtdt
real(kind=kind_phys), intent(in ), dimension(:,:,:) :: dqdt
logical, intent(in) :: qdiag3d
logical, intent(in) :: oz_phys_2015
logical, intent(in) :: oz_phys_2006
type(ty_ozphys), intent(in) :: ozphys

! Outputs (optional)
real(kind=kind_phys), intent(inout), dimension(:,:), pointer, optional :: &
real(kind=kind_phys), intent(inout), dimension(:,:) :: &
do3_dt_prd, & ! Physics tendency: production and loss effect
do3_dt_ozmx, & ! Physics tendency: ozone mixing ratio effect
do3_dt_temp, & ! Physics tendency: temperature effect
Expand All @@ -50,7 +51,7 @@ subroutine GFS_suite_stateout_update_run (im, levs, ntrac, dtp, tgrs, ugrs, vgrs

! Locals
integer :: i, k

! Initialize CCPP error handling variables
errmsg = ''
errflg = 0
Expand All @@ -65,12 +66,12 @@ subroutine GFS_suite_stateout_update_run (im, levs, ntrac, dtp, tgrs, ugrs, vgrs
! If using photolysis physics schemes, update (prognostic) gas concentrations using
! updated state.
if (oz_phys_2015) then
call ozphys%run_o3prog_2015(con_1ovg, dtp, prsl, gt0, dp, ozpl, oz0, do3_dt_prd, &
do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
call ozphys%run_o3prog_2015(con_1ovg, dtp, prsl, gt0, dp, ozpl, oz0, qdiag3d, &
do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
endif
if (oz_phys_2006) then
call ozphys%run_o3prog_2006(con_1ovg, dtp, prsl, gt0, dp, ozpl, oz0, do3_dt_prd, &
do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
call ozphys%run_o3prog_2006(con_1ovg, dtp, prsl, gt0, dp, ozpl, oz0, qdiag3d, &
do3_dt_prd, do3_dt_ozmx, do3_dt_temp, do3_dt_ohoz)
endif

! If using Ferrier-Aligo microphysics, set bounds on the mass-weighted rime factor.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,13 @@
dimensions = ()
type = ty_ozphys
intent = in
[qdiag3d]
standard_name = flag_for_tracer_diagnostics_3D
long_name = flag for 3d tracer diagnostic fields
units = flag
dimensions = ()
type = logical
intent = in
[oz_phys_2015]
standard_name = flag_for_nrl_2015_ozone_scheme
long_name = flag for new (2015) ozone physics
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -61,8 +61,7 @@ end subroutine GFS_surface_generic_pre_init
!!
subroutine GFS_surface_generic_pre_run (nthreads, im, levs, vfrac, islmsk, isot, ivegsrc, stype, scolor,vtype, slope, &
prsik_1, prslk_1, tsfc, phil, con_g, sigmaf, work3, zlvl, &
drain_cpl, dsnow_cpl, rain_cpl, snow_cpl, lndp_type, n_var_lndp, sfc_wts, &
lndp_var_list, lndp_prt_list, &
lndp_type, n_var_lndp, sfc_wts, lndp_var_list, lndp_prt_list, &
z01d, zt1d, bexp1d, xlai1d, vegf1d, lndp_vgf, &
cplflx, flag_cice, islmsk_cice, slimskin_cpl, &
wind, u1, v1, cnvwind, smcwlt2, smcref2, vtype_save, stype_save,scolor_save, slope_save, &
Expand All @@ -87,10 +86,6 @@ subroutine GFS_surface_generic_pre_run (nthreads, im, levs, vfrac, islmsk, isot,
real(kind=kind_phys), dimension(:), intent(inout) :: sigmaf, work3, zlvl

! Stochastic physics / surface perturbations
real(kind=kind_phys), dimension(:), intent(out) :: drain_cpl
real(kind=kind_phys), dimension(:), intent(out) :: dsnow_cpl
real(kind=kind_phys), dimension(:), intent(in) :: rain_cpl
real(kind=kind_phys), dimension(:), intent(in) :: snow_cpl
integer, intent(in) :: lndp_type, n_var_lndp
character(len=3), dimension(:), intent(in) :: lndp_var_list
real(kind=kind_phys), dimension(:), intent(in) :: lndp_prt_list
Expand Down
32 changes: 0 additions & 32 deletions physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_generic_pre.meta
Original file line number Diff line number Diff line change
Expand Up @@ -290,38 +290,6 @@
type = real
kind = kind_phys
intent = inout
[drain_cpl]
standard_name = tendency_of_lwe_thickness_of_rain_amount_on_dynamics_timestep_for_coupling
long_name = change in rain_cpl (coupling_type)
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[dsnow_cpl]
standard_name = tendency_of_lwe_thickness_of_snowfall_amount_on_dynamics_timestep_for_coupling
long_name = change in show_cpl (coupling_type)
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[rain_cpl]
standard_name = cumulative_lwe_thickness_of_precipitation_amount_for_coupling
long_name = total rain precipitation
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[snow_cpl]
standard_name = cumulative_lwe_thickness_of_snow_amount_for_coupling
long_name = total snow precipitation
units = m
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[lndp_type]
standard_name = control_for_stochastic_land_surface_perturbation
long_name = index for stochastic land surface perturbations type
Expand Down
8 changes: 4 additions & 4 deletions physics/Interstitials/UFS_SCM_NEPTUNE/dcyc2t3.f
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module dcyc2t3
! input/output: !
! dtdt,dtdtnp, !
! outputs: !
! adjsfcdsw,adjsfcnsw,adjsfcdlw,adjsfculw, !
! adjsfcdsw,adjsfcnsw,adjsfcdlw, !
! adjsfculw_lnd,adjsfculw_ice,adjsfculw_wat,xmu,xcosz, !
! adjnirbmu,adjnirdfu,adjvisbmu,adjvisdfu, !
! adjdnnbmd,adjdnndfd,adjdnvbmd,adjdnvdfd) !
Expand Down Expand Up @@ -181,7 +181,7 @@ subroutine dcyc2t3_run &
! --- input/output:
& dtdt,dtdtnp,htrlw, &
! --- outputs:
& adjsfcdsw,adjsfcnsw,adjsfcdlw,adjsfculw, &
& adjsfcdsw,adjsfcnsw,adjsfcdlw, &
& adjsfculw_lnd,adjsfculw_ice,adjsfculw_wat,xmu,xcosz, &
& adjnirbmu,adjnirdfu,adjvisbmu,adjvisdfu, &
& adjnirbmd,adjnirdfd,adjvisbmd,adjvisdfd, &
Expand Down Expand Up @@ -242,7 +242,7 @@ subroutine dcyc2t3_run &

! --- outputs:
real(kind=kind_phys), dimension(:), intent(out) :: &
& adjsfcdsw, adjsfcnsw, adjsfcdlw, adjsfculw, xmu, xcosz, &
& adjsfcdsw, adjsfcnsw, adjsfcdlw, xmu, xcosz, &
& adjnirbmu, adjnirdfu, adjvisbmu, adjvisdfu, &
& adjnirbmd, adjnirdfd, adjvisbmd, adjvisdfd

Expand Down Expand Up @@ -352,7 +352,7 @@ subroutine dcyc2t3_run &

! if (lprnt .and. i == ipr) write(0,*)' in dcyc3: dry==',dry(i)
! &,' wet=',wet(i),' icy=',icy(i),' tsfc3=',tsfc3(i,:)
! &,' sfcemis=',sfcemis(i,:),' adjsfculw=',adjsfculw(i,:)
! &,' sfcemis=',sfcemis(i,:)
!

!> - normalize by average value over radiation period for daytime.
Expand Down
8 changes: 0 additions & 8 deletions physics/Interstitials/UFS_SCM_NEPTUNE/dcyc2t3.meta
Original file line number Diff line number Diff line change
Expand Up @@ -524,14 +524,6 @@
type = real
kind = kind_phys
intent = out
[adjsfculw]
standard_name = surface_upwelling_longwave_flux
long_name = surface upwelling longwave flux at current time
units = W m-2
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = out
[adjsfculw_lnd]
standard_name = surface_upwelling_longwave_flux_over_land
long_name = surface upwelling longwave flux at current time over land
Expand Down
2 changes: 1 addition & 1 deletion physics/MP/Morrison_Gettelman/aerinterp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -426,7 +426,7 @@ SUBROUTINE aerinterpol( me,master,nthrds,npts,IDATE,FHOUR,iflip, jindx1,jindx2,
ENDDO
else
DO k=1, levsaer-1 !! from sfc to toa
IF(prsl(j,L) < aerpres(j,k) .and. prsl(j,L)>aerpres(j,k+1)) then
IF(prsl(j,L) <= aerpres(j,k) .and. prsl(j,L)>aerpres(j,k+1)) then
i1 = k
i2 = min(k+1,levsaer)
exit
Expand Down
Loading

0 comments on commit e399c22

Please sign in to comment.