Skip to content

Commit

Permalink
Merge branch 'ufs-community:ufs/dev' into production/RRFS.v1-mynn
Browse files Browse the repository at this point in the history
  • Loading branch information
haiqinli authored Mar 8, 2024
2 parents 274a696 + cc114f4 commit 0697f26
Show file tree
Hide file tree
Showing 22 changed files with 291 additions and 144 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
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 @@ -42,9 +42,9 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid, iopt_lake, iopt_l
real(kind=kind_phys), dimension(:), intent(in ) :: landfrac, lakefrac, lakedepth, oceanfrac
real(kind=kind_phys), dimension(:), intent(inout) :: cice, hice
real(kind=kind_phys), dimension(:), intent( out) :: frland
real(kind=kind_phys), dimension(:), intent(in ) :: snowd, tprcp, uustar, weasd, qss
real(kind=kind_phys), dimension(:), intent(in ) :: snowd, tprcp, uustar, weasd, qss, tisfc

real(kind=kind_phys), dimension(:), intent(inout) :: tsfc, tsfco, tsfcl, tisfc
real(kind=kind_phys), dimension(:), intent(inout) :: tsfc, tsfco, tsfcl
real(kind=kind_phys), dimension(:), intent(inout) :: snowd_lnd, snowd_ice, tprcp_wat, &
tprcp_lnd, tprcp_ice, tsfc_wat, tsurf_wat,tsurf_lnd, tsurf_ice, &
uustar_wat, uustar_lnd, uustar_ice, weasd_lnd, weasd_ice, &
Expand Down Expand Up @@ -86,7 +86,6 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid, iopt_lake, iopt_l
if (oceanfrac(i) > zero) then
if (cice(i) >= min_seaice) then
icy(i) = .true.
tisfc(i) = max(timin, min(tisfc(i), tgice))
if (cplflx) then
islmsk_cice(i) = 4
flag_cice(i) = .true.
Expand All @@ -111,7 +110,6 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid, iopt_lake, iopt_l
if (cice(i) >= min_lakeice) then
icy(i) = .true.
islmsk(i) = 2
tisfc(i) = max(timin, min(tisfc(i), tgice))
else
cice(i) = zero
hice(i) = zero
Expand Down Expand Up @@ -151,7 +149,6 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid, iopt_lake, iopt_l
if (oceanfrac(i) > zero) then
if (cice(i) >= min_seaice) then
icy(i) = .true.
tisfc(i) = max(timin, min(tisfc(i), tgice))
! This cplice namelist option was added to deal with the
! situation of the FV3ATM-HYCOM coupling without an active sea
! ice (e.g., CICE6) component. By default, the cplice is true
Expand Down Expand Up @@ -187,9 +184,6 @@ subroutine GFS_surface_composites_pre_run (im, lkm, frac_grid, iopt_lake, iopt_l
is_clm = lkm>0 .and. iopt_lake==iopt_lake_clm .and. use_lake_model(i)>0
if (cice(i) >= min_lakeice) then
icy(i) = .true.
if(.not.is_clm) then
tisfc(i) = max(timin, min(tisfc(i), tgice))
endif
islmsk(i) = 2
else
cice(i) = zero
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -358,7 +358,7 @@
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = inout
intent = in
[tsurf_wat]
standard_name = surface_skin_temperature_after_iteration_over_water
long_name = surface skin temperature after iteration over water
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
17 changes: 13 additions & 4 deletions physics/PBL/SATMEDMF/satmedmfvdifq.F
Original file line number Diff line number Diff line change
Expand Up @@ -75,8 +75,8 @@ end subroutine satmedmfvdifq_init
!! \section detail_satmedmfvidfq GFS satmedmfvdifq Detailed Algorithm
subroutine satmedmfvdifq_run(im,km,ntrac,ntcw,ntrw, &
& ntiw,ntke,grav,rd,cp,rv,hvap,hfus,fv,eps,epsm1, &
& dv,du,tdt,rtg,u1,v1,t1,q1,swh,hlw,xmu, &
& garea,zvfun,sigmaf, &
& dv,du,tdt,rtg,u1,v1,t1,q1,usfco,vsfco,icplocn2atm, &
& swh,hlw,xmu,garea,zvfun,sigmaf, &
& psk,rbsoil,zorl,u10m,v10m,fm,fh, &
& tsea,heat,evap,stress,spd1,kpbl, &
& prsi,del,prsl,prslk,phii,phil,delt, &
Expand Down Expand Up @@ -110,6 +110,7 @@ subroutine satmedmfvdifq_run(im,km,ntrac,ntcw,ntrw, &
& tdt(:,:), rtg(:,:,:)
real(kind=kind_phys), intent(in) :: &
& u1(:,:), v1(:,:), &
& usfco(:), vsfco(:), &
& t1(:,:), q1(:,:,:), &
& swh(:,:), hlw(:,:), &
& xmu(:), garea(:), &
Expand All @@ -126,6 +127,7 @@ subroutine satmedmfvdifq_run(im,km,ntrac,ntcw,ntrw, &
real(kind=kind_phys), intent(inout), dimension(:,:,:) :: dtend
integer, intent(in) :: dtidx(:,:), index_of_temperature, &
& index_of_x_wind, index_of_y_wind, index_of_process_pbl
integer, intent(in) :: icplocn2atm
real(kind=kind_phys), intent(out) :: &
& dusfc(:), dvsfc(:), &
& dtsfc(:), dqsfc(:), &
Expand All @@ -142,6 +144,7 @@ subroutine satmedmfvdifq_run(im,km,ntrac,ntcw,ntrw, &
!----------------------------------------------------------------------
!***
!*** local variables
real(kind=kind_phys) spd1_m
!***
integer i,is,k,n,ndt,km1,kmpbl,kmscu,ntrac1,idtend
integer kps,kbx,kmx
Expand Down Expand Up @@ -2376,8 +2379,14 @@ subroutine satmedmfvdifq_run(im,km,ntrac,ntcw,ntrw, &
enddo
enddo
do i = 1,im
dusfc(i) = -1.*rho_a(i)*stress(i)*u1(i,1)/spd1(i)
dvsfc(i) = -1.*rho_a(i)*stress(i)*v1(i,1)/spd1(i)
if(icplocn2atm == 0) then
dusfc(i) = -1.*rho_a(i)*stress(i)*u1(i,1)/spd1(i)
dvsfc(i) = -1.*rho_a(i)*stress(i)*v1(i,1)/spd1(i)
else if (icplocn2atm ==1) then
spd1_m=sqrt( (u1(i,1)-usfco(i))**2+(v1(i,1)-vsfco(i))**2 )
dusfc(i) = -1.*rho_a(i)*stress(i)*(u1(i,1)-usfco(i))/spd1_m
dvsfc(i) = -1.*rho_a(i)*stress(i)*(v1(i,1)-vsfco(i))/spd1_m
endif
enddo
!
if(ldiag3d .and. .not. gen_tend) then
Expand Down
23 changes: 23 additions & 0 deletions physics/PBL/SATMEDMF/satmedmfvdifq.meta
Original file line number Diff line number Diff line change
Expand Up @@ -217,6 +217,29 @@
type = real
kind = kind_phys
intent = in
[usfco]
standard_name = x_ocean_current
long_name = zonal current at ocean surface
units = m s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[vsfco]
standard_name = y_ocean_current
long_name = meridional current at ocean surface
units = m s-1
dimensions = (horizontal_loop_extent)
type = real
kind = kind_phys
intent = in
[icplocn2atm]
standard_name = control_for_air_sea_flux_computation_over_water
long_name = air-sea flux option
units = 1
dimensions = ()
type = integer
intent = in
[t1]
standard_name = air_temperature
long_name = layer mean air temperature
Expand Down
Loading

0 comments on commit 0697f26

Please sign in to comment.