Skip to content

Commit cdc11de

Browse files
authored
Merge pull request #1096 from grantfirl/ufs-dev-PR220
UFS-dev PR#220
2 parents f458bf4 + c8891df commit cdc11de

File tree

10 files changed

+298
-205
lines changed

10 files changed

+298
-205
lines changed

CMakeLists.txt

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -140,11 +140,12 @@ SET_PROPERTY(SOURCE ${SCHEMES} ${CAPS}
140140
APPEND_STRING PROPERTY COMPILE_FLAGS " ${CMAKE_Fortran_FLAGS_PHYSICS} ${OpenMP_Fortran_FLAGS}")
141141

142142
# Lower optimization for certain schemes when compiling with Intel in Release mode
143-
if(CMAKE_BUILD_TYPE STREQUAL "Release" AND ${CMAKE_Fortran_COMPILER_ID} STREQUAL "Intel")
143+
if(CMAKE_BUILD_TYPE STREQUAL "Release" AND (${CMAKE_Fortran_COMPILER_ID} STREQUAL "Intel" OR ${CMAKE_Fortran_COMPILER_ID} STREQUAL "IntelLLVM"))
144144
# Define a list of schemes that need lower optimization with Intel in Release mode
145145
set(SCHEME_NAMES_LOWER_OPTIMIZATION module_sf_mynn.F90
146146
mynnedmf_wrapper.F90
147-
gcycle.F90)
147+
gcycle.F90
148+
module_mp_nssl_2mom.F90)
148149
foreach(SCHEME_NAME IN LISTS SCHEME_NAMES_LOWER_OPTIMIZATION)
149150
set(SCHEMES_TMP ${SCHEMES})
150151
# Need to determine the name of the scheme with its path
@@ -156,7 +157,7 @@ if(CMAKE_BUILD_TYPE STREQUAL "Release" AND ${CMAKE_Fortran_COMPILER_ID} STREQUAL
156157
endif()
157158

158159
# No optimization for certain schemes when compiling with Intel in Release mode
159-
if(CMAKE_BUILD_TYPE STREQUAL "Release" AND ${CMAKE_Fortran_COMPILER_ID} STREQUAL "Intel")
160+
if(CMAKE_BUILD_TYPE STREQUAL "Release" AND (${CMAKE_Fortran_COMPILER_ID} STREQUAL "Intel" OR ${CMAKE_Fortran_COMPILER_ID} STREQUAL "IntelLLVM"))
160161
# Define a list of schemes that can't be optimized with Intel in Release mode
161162
set(SCHEME_NAMES_NO_OPTIMIZATION GFS_typedefs.F90)
162163
foreach(SCHEME_NAME IN LISTS SCHEME_NAMES_NO_OPTIMIZATION)

CODEOWNERS

Lines changed: 180 additions & 180 deletions
Large diffs are not rendered by default.

physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_composites_post.F90

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -23,22 +23,22 @@ module GFS_surface_composites_post
2323
!! \htmlinclude GFS_surface_composites_post_run.html
2424
!!
2525
subroutine GFS_surface_composites_post_run ( &
26-
im, kice, km, rd, rvrdm1, cplflx, cplwav2atm, frac_grid, flag_cice, thsfc_loc, islmsk, dry, wet, icy, wind, t1, q1, prsl1, &
26+
im, kice, km, rd, rvrdm1, cplflx, cplwav2atm, cpl_fire, frac_grid, flag_cice, thsfc_loc, islmsk, dry, wet, icy, wind, t1, q1, prsl1, &
2727
landfrac, lakefrac, oceanfrac, zorl, zorlo, zorll, zorli, garea, frac_ice, &
2828
cd, cd_wat, cd_lnd, cd_ice, cdq, cdq_wat, cdq_lnd, cdq_ice, rb, rb_wat, rb_lnd, rb_ice, stress, stress_wat, stress_lnd, &
2929
stress_ice, ffmm, ffmm_wat, ffmm_lnd, ffmm_ice, ffhh, ffhh_wat, ffhh_lnd, ffhh_ice, uustar, uustar_wat, uustar_lnd, &
3030
uustar_ice, fm10, fm10_wat, fm10_lnd, fm10_ice, fh2, fh2_wat, fh2_lnd, fh2_ice, tsurf_wat, tsurf_lnd, tsurf_ice, &
3131
cmm, cmm_wat, cmm_lnd, cmm_ice, chh, chh_wat, chh_lnd, chh_ice, gflx, gflx_wat, gflx_lnd, gflx_ice, ep1d, ep1d_wat, &
3232
ep1d_lnd, ep1d_ice, weasd, weasd_lnd, weasd_ice, snowd, snowd_lnd, snowd_ice, tprcp, tprcp_wat, &
33-
tprcp_lnd, tprcp_ice, evap, evap_wat, evap_lnd, evap_ice, hflx, hflx_wat, hflx_lnd, hflx_ice, qss, qss_wat, qss_lnd, &
34-
qss_ice, tsfc, tsfco, tsfcl, tsfc_wat, tisfc, hice, cice, tiice, &
33+
tprcp_lnd, tprcp_ice, evap, evap_wat, evap_lnd, evap_ice, hflx, hflx_wat, hflx_lnd, hflx_ice, hflx_fire, evap_fire, &
34+
qss, qss_wat, qss_lnd, qss_ice, tsfc, tsfco, tsfcl, tsfc_wat, tisfc, hice, cice, tiice, &
3535
sigmaf, zvfun, lheatstrg, h0facu, h0facs, hflxq, hffac, stc, lkm, iopt_lake, iopt_lake_clm, use_lake_model, &
3636
grav, prsik1, prslk1, prslki, z1, ztmax_wat, ztmax_lnd, ztmax_ice, huge, errmsg, errflg)
3737

3838
implicit none
3939

4040
integer, intent(in) :: im, kice, km, lkm, iopt_lake, iopt_lake_clm
41-
logical, intent(in) :: cplflx, frac_grid, cplwav2atm, frac_ice
41+
logical, intent(in) :: cplflx, frac_grid, cplwav2atm, frac_ice, cpl_fire
4242
logical, intent(in) :: lheatstrg
4343
logical, dimension(:), intent(in) :: flag_cice, dry, icy
4444
logical, dimension(:), intent(in) :: wet
@@ -51,6 +51,7 @@ subroutine GFS_surface_composites_post_run (
5151
snowd_lnd, snowd_ice, tprcp_wat, tprcp_lnd, tprcp_ice, evap_wat, evap_lnd, evap_ice, hflx_wat, hflx_lnd, &
5252
hflx_ice, qss_wat, qss_lnd, qss_ice, tsfc_wat, zorlo, zorll, zorli, garea
5353

54+
real(kind=kind_phys), dimension(:), intent(in), optional :: hflx_fire, evap_fire
5455
real(kind=kind_phys), dimension(:), intent(inout) :: zorl, cd, cdq, rb, stress, ffmm, ffhh, uustar, fm10, &
5556
fh2, cmm, chh, gflx, ep1d, weasd, snowd, tprcp, evap, hflx, qss, tsfc, tsfco, tsfcl, tisfc
5657

@@ -275,6 +276,10 @@ subroutine GFS_surface_composites_post_run (
275276
else if (islmsk(i) == 1) then
276277
!-- land
277278
call composite_land
279+
if (cpl_fire) then
280+
hflx(i) = hflx(i) + hflx_fire(i)
281+
evap(i) = evap(i) + evap_fire(i)
282+
endif
278283
elseif (islmsk(i) == 0) then
279284
!-- water
280285
call composite_wet

physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_composites_post.meta

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -816,6 +816,31 @@
816816
type = real
817817
kind = kind_phys
818818
intent = in
819+
[hflx_fire]
820+
standard_name = kinematic_surface_upward_sensible_heat_flux_of_fire
821+
long_name = kinematic surface upward sensible heat flux of fire
822+
units = K m s-1
823+
dimensions = (horizontal_loop_extent)
824+
type = real
825+
kind = kind_phys
826+
intent = in
827+
optional = True
828+
[evap_fire]
829+
standard_name = surface_upward_specific_humidity_flux_of_fire
830+
long_name = kinematic surface upward latent heat flux of fire
831+
units = kg kg-1 m s-1
832+
dimensions = (horizontal_loop_extent)
833+
type = real
834+
kind = kind_phys
835+
intent = in
836+
optional = True
837+
[cpl_fire]
838+
standard_name = do_fire_coupling
839+
long_name = flag controlling fire_behavior collection (default off)
840+
units = flag
841+
dimensions = ()
842+
type = logical
843+
intent = in
819844
[qss]
820845
standard_name = surface_specific_humidity
821846
long_name = surface air saturation specific humidity

physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_generic_post.F90

Lines changed: 13 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ end subroutine GFS_surface_generic_post_init
4545
!> \section arg_table_GFS_surface_generic_post_run Argument Table
4646
!! \htmlinclude GFS_surface_generic_post_run.html
4747
!!
48-
subroutine GFS_surface_generic_post_run (im, cplflx, cplaqm, cplchm, cplwav, cpllnd, lssav, dry, icy, wet, &
48+
subroutine GFS_surface_generic_post_run (im, cplflx, cplaqm, cplchm, cplwav, cpllnd, cpl_fire, lssav, dry, icy, wet, &
4949
lsm, lsm_noahmp, dtf, ep1d, gflx, tgrs_1, qgrs_1, ugrs_1, vgrs_1, &
5050
adjsfcdlw, adjsfcdsw, adjnirbmd, adjnirdfd, adjvisbmd, adjvisdfd, adjsfculw, adjsfculw_wat, adjnirbmu, adjnirdfu, &
5151
adjvisbmu, adjvisdfu, t2m, q2m, u10m, v10m, tsfc, tsfc_wat, pgr, xcosz, evbs, evcw, trans, sbsno, snowc, snohf, pah, pahi, &
@@ -59,7 +59,7 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplaqm, cplchm, cplwav, cpl
5959
implicit none
6060

6161
integer, intent(in) :: im
62-
logical, intent(in) :: cplflx, cplaqm, cplchm, cplwav, cpllnd, lssav
62+
logical, intent(in) :: cplflx, cplaqm, cplchm, cplwav, cpllnd, cpl_fire, lssav
6363
logical, dimension(:), intent(in) :: dry, icy, wet
6464
integer, intent(in) :: lsm, lsm_noahmp
6565
real(kind=kind_phys), intent(in) :: dtf
@@ -136,9 +136,20 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplaqm, cplchm, cplwav, cpl
136136
dswsfci_cpl (i) = adjsfcdsw(i)
137137
dlwsfc_cpl (i) = dlwsfc_cpl(i) + adjsfcdlw(i)*dtf
138138
dswsfc_cpl (i) = dswsfc_cpl(i) + adjsfcdsw(i)*dtf
139+
enddo
140+
endif
141+
142+
if (cplflx .or. cpllnd .or. cpl_fire) then
143+
do i=1,im
139144
psurfi_cpl (i) = pgr(i)
140145
enddo
141146
endif
147+
if (cplflx .or. cpl_fire) then
148+
do i=1,im
149+
t2mi_cpl (i) = t2m(i)
150+
q2mi_cpl (i) = q2m(i)
151+
enddo
152+
endif
142153

143154
if (cplflx) then
144155
do i=1,im
@@ -155,8 +166,6 @@ subroutine GFS_surface_generic_post_run (im, cplflx, cplaqm, cplchm, cplwav, cpl
155166
nlwsfci_cpl(i) = adjsfcdlw(i) - adjsfculw_wat(i)
156167
endif
157168
nlwsfc_cpl (i) = nlwsfc_cpl(i) + nlwsfci_cpl(i)*dtf
158-
t2mi_cpl (i) = t2m(i)
159-
q2mi_cpl (i) = q2m(i)
160169
enddo
161170
endif
162171

physics/Interstitials/UFS_SCM_NEPTUNE/GFS_surface_generic_post.meta

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -126,6 +126,13 @@
126126
dimensions = ()
127127
type = logical
128128
intent = in
129+
[cpl_fire]
130+
standard_name = do_fire_coupling
131+
long_name = flag controlling fire_behavior collection (default off)
132+
units = flag
133+
dimensions = ()
134+
type = logical
135+
intent = in
129136
[lssav]
130137
standard_name = flag_for_diagnostics
131138
long_name = logical flag for storing diagnostics

physics/Interstitials/UFS_SCM_NEPTUNE/gcycle.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,7 @@ subroutine gcycle (me, nthrds, nx, ny, isc, jsc, nsst, tile_num, nlunit, fn_nml,
107107
real (kind=kind_io8) :: min_ice(nx*ny)
108108
integer :: i_indx(nx*ny), j_indx(nx*ny)
109109
character(len=6) :: tile_num_ch
110-
real(kind=kind_phys) :: sig1t
110+
real(kind=kind_phys) :: sig1t(nx*ny)
111111
integer :: npts, nb, ix, jx, ls, ios, ll
112112
logical :: exists
113113

physics/MP/Morrison_Gettelman/aerinterp.F90

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -282,7 +282,7 @@ SUBROUTINE aerinterpol( me,master,nthrds,npts,IDATE,FHOUR,iflip, jindx1,jindx2,
282282
character(*), intent(inout) :: errmsg
283283
integer, intent(in) :: iflip
284284
integer i1,i2, iday,j,j1,j2,l,npts,nc,n1,n2,lev,k,i,ii, klev
285-
real(kind=kind_phys) fhour,temj, tx1, tx2,temi, tem
285+
real(kind=kind_phys) fhour,temj, tx1, tx2,temi, tem, tem1, tem2
286286
real(kind=kind_phys), dimension(npts) :: temij,temiy,temjx,ddxy
287287

288288
!
@@ -363,10 +363,9 @@ SUBROUTINE aerinterpol( me,master,nthrds,npts,IDATE,FHOUR,iflip, jindx1,jindx2,
363363
!$OMP parallel num_threads(nthrds) default(none) &
364364
!$OMP shared(npts,ntrcaer,aerin,aer_pres,prsl) &
365365
!$OMP shared(ddx,ddy,jindx1,jindx2,iindx1,iindx2) &
366-
!$OMP shared(aerpm,aerpres,aerout,lev,nthrds) &
367-
!$OMP shared(temij,temiy,temjx,ddxy) &
368-
!$OMP private(l,j,k,ii,i1,i2,j1,j2,tem) &
369-
!$OMP copyin(tx1,tx2) firstprivate(tx1,tx2)
366+
!$OMP shared(aerpm,aerpres,aerout,lev,nthrds) &
367+
!$OMP shared(temij,temiy,temjx,ddxy,tx1,tx2) &
368+
!$OMP private(l,j,k,ii,i1,i2,j1,j2,tem,tem1,tem2)
370369

371370
!$OMP do
372371
#endif
@@ -416,10 +415,10 @@ SUBROUTINE aerinterpol( me,master,nthrds,npts,IDATE,FHOUR,iflip, jindx1,jindx2,
416415
ENDIF
417416
ENDDO
418417
tem = 1.0 / (aerpres(j,i1) - aerpres(j,i2))
419-
tx1 = (prsl(j,L) - aerpres(j,i2)) * tem
420-
tx2 = (aerpres(j,i1) - prsl(j,L)) * tem
418+
tem1 = (prsl(j,L) - aerpres(j,i2)) * tem
419+
tem2 = (aerpres(j,i1) - prsl(j,L)) * tem
421420
DO ii = 1, ntrcaer
422-
aerout(j,L,ii) = aerpm(j,i1,ii)*tx1 + aerpm(j,i2,ii)*tx2
421+
aerout(j,L,ii) = aerpm(j,i1,ii)*tem1 + aerpm(j,i2,ii)*tem2
423422
ENDDO
424423
endif
425424
ENDDO !L-loop

physics/smoke_dust/rrfs_smoke_wrapper.F90

Lines changed: 22 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -109,28 +109,30 @@ end subroutine rrfs_smoke_wrapper_init
109109
!!
110110
!>\section rrfs_smoke_wrapper rrfs-sd Scheme General Algorithm
111111
!> @{
112-
subroutine rrfs_smoke_wrapper_run(im, kte, kme, ktau, dt, garea, land, jdate, &
112+
subroutine rrfs_smoke_wrapper_run(im, flag_init, kte, kme, ktau, dt, garea, land, jdate, &
113113
u10m, v10m, ustar, rlat, rlon, tskin, pb2d, t2m, dpt2m, &
114114
pr3d, ph3d,phl3d, prl3d, tk3d, us3d, vs3d, spechum, w, &
115115
nsoil, smc, tslb, vegtype_dom, vegtype_frac, soiltyp, nlcat, &
116-
dswsfc, zorl, snow, julian,recmol, &
116+
dswsfc, zorl, snow, julian, recmol, &
117117
idat, rain_cpl, rainc_cpl, hf2d, g, pi, con_cp, con_rd, con_fv, &
118118
dust12m_in, emi_ant_in, smoke_RRFS, smoke2d_RRFS, &
119119
ntrac, qgrs, gq0, chem3d, tile_num, &
120-
ntsmoke, ntdust, ntcoarsepm, imp_physics, imp_physics_thompson, &
120+
ntfsmoke, ntsmoke, ntdust, ntcoarsepm, &
121+
imp_physics, imp_physics_thompson, &
121122
nwfa, nifa, emanoc, emdust, emseas, drydep_flux_out, wetdpr, &
122123
ebb_smoke_in, frp_output, coef_bb, fire_type_out, &
123124
ebu_smoke,fhist,min_fplume, &
124125
max_fplume, hwp, hwp_ave, wetness, ndvel, ddvel_inout, &
126+
smoke_fire, cpl_fire, &
125127
peak_hr_out,lu_nofire_out,lu_qfire_out, &
126128
fire_heat_flux_out, frac_grid_burned_out, kpbl,oro, &
127129
uspdavg, hpbl_thetav, mpicomm, mpirank, mpiroot, errmsg,errflg )
128-
129130
implicit none
130131

131132

132133
integer, intent(in) :: im,kte,kme,ktau,nsoil,tile_num,jdate(8),idat(8)
133-
integer, intent(in) :: ntrac, ntsmoke, ntdust, ntcoarsepm, ndvel, nlcat
134+
integer, intent(in) :: ntrac, ntfsmoke, ntsmoke, ntdust, ntcoarsepm, ndvel, nlcat
135+
logical, intent(in) :: flag_init
134136
real(kind_phys),intent(in) :: dt, julian, g, pi, con_cp, con_rd, con_fv
135137

136138
integer, parameter :: ids=1,jds=1,jde=1, kds=1
@@ -165,6 +167,8 @@ subroutine rrfs_smoke_wrapper_run(im, kte, kme, ktau, dt, garea, land, jdate,
165167
real(kind_phys), dimension(:), intent(in), optional :: wetness
166168
real(kind_phys), dimension(:), intent(out), optional :: lu_nofire_out,lu_qfire_out
167169
integer, dimension(:), intent(out), optional :: fire_type_out
170+
real(kind_phys), dimension(:), intent(in), optional :: smoke_fire
171+
logical, intent(in) :: cpl_fire
168172
integer, intent(in) :: imp_physics, imp_physics_thompson
169173
integer, dimension(:), intent(in) :: kpbl
170174
real(kind_phys), dimension(:), intent(in) :: oro
@@ -234,6 +238,19 @@ subroutine rrfs_smoke_wrapper_run(im, kte, kme, ktau, dt, garea, land, jdate,
234238
errmsg = ''
235239
errflg = 0
236240

241+
if (cpl_fire) then
242+
if (flag_init) then
243+
do i=1,im
244+
do k=kts,kte
245+
qgrs(i,k,ntfsmoke) = 0.
246+
end do
247+
end do
248+
endif
249+
do i=1,im
250+
qgrs(i,kts,ntfsmoke) = qgrs(i,kts,ntfsmoke) + smoke_fire(i)
251+
end do
252+
endif
253+
237254
if (.not. do_rrfs_sd) return
238255

239256
! -- set domain

physics/smoke_dust/rrfs_smoke_wrapper.meta

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -200,6 +200,13 @@
200200
dimensions = ()
201201
type = integer
202202
intent = in
203+
[flag_init]
204+
standard_name = flag_for_first_timestep
205+
long_name = flag signaling first time step for time integration loop
206+
units = flag
207+
dimensions = ()
208+
type = logical
209+
intent = in
203210
[kte]
204211
standard_name = vertical_layer_dimension
205212
long_name = vertical layer dimension
@@ -642,6 +649,13 @@
642649
dimensions = ()
643650
type = integer
644651
intent = in
652+
[ntfsmoke]
653+
standard_name = index_for_fire_smoke_in_tracer_concentration_array
654+
long_name = tracer index for fire smoke
655+
units = index
656+
dimensions = ()
657+
type = integer
658+
intent = in
645659
[ntdust]
646660
standard_name = index_for_dust_in_tracer_concentration_array
647661
long_name = tracer index for dust
@@ -946,6 +960,22 @@
946960
type = real
947961
kind = kind_phys
948962
intent = in
963+
[smoke_fire]
964+
standard_name = smoke_emission_of_fire
965+
long_name = smoke emission of fire
966+
units = kg m-2
967+
dimensions = (horizontal_loop_extent)
968+
type = real
969+
kind = kind_phys
970+
intent = in
971+
optional = True
972+
[cpl_fire]
973+
standard_name = do_fire_coupling
974+
long_name = flag controlling fire_behavior collection (default off)
975+
units = flag
976+
dimensions = ()
977+
type = logical
978+
intent = in
949979
[errmsg]
950980
standard_name = ccpp_error_message
951981
long_name = error message for error handling in CCPP

0 commit comments

Comments
 (0)