Skip to content

Commit 24643b0

Browse files
authored
Merge pull request NCAR#237 from grantfirl/rrfsv1-to-ufs/dev8
Eighth reconciliation PR from production/RRFS.v1
2 parents a7fe01c + fa3f1ce commit 24643b0

File tree

4 files changed

+58
-37
lines changed

4 files changed

+58
-37
lines changed

physics/smoke_dust/module_add_emiss_burn.F90

+24-22
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ subroutine add_emis_burn(dtstep,dz8w,rho_phy,pi,ebb_min, &
1212
coef_bb_dc, fire_hist, hwp, hwp_prevd, &
1313
swdown,ebb_dcycle, ebu_in, ebu,fire_type,&
1414
q_vap, add_fire_moist_flux, &
15+
sc_factor, &
1516
ids,ide, jds,jde, kds,kde, &
1617
ims,ime, jms,jme, kms,kme, &
1718
its,ite, jts,jte, kts,kte,mpiid )
@@ -34,7 +35,6 @@ subroutine add_emis_burn(dtstep,dz8w,rho_phy,pi,ebb_min, &
3435
real(kind_phys), DIMENSION(ims:ime,jms:jme), INTENT(IN) :: hwp, peak_hr, fire_end_hr, ebu_in !RAR: Shall we make fire_end integer?
3536
real(kind_phys), DIMENSION(ims:ime,jms:jme), INTENT(INOUT) :: coef_bb_dc ! RAR:
3637
real(kind_phys), DIMENSION(ims:ime,jms:jme), INTENT(IN) :: hwp_prevd
37-
3838
real(kind_phys), DIMENSION(ims:ime,kms:kme,jms:jme), INTENT(IN) :: dz8w,rho_phy !,rel_hum
3939
real(kind_phys), INTENT(IN) :: dtstep, gmt
4040
real(kind_phys), INTENT(IN) :: time_int, pi, ebb_min ! RAR: time in seconds since start of simulation
@@ -55,12 +55,17 @@ subroutine add_emis_burn(dtstep,dz8w,rho_phy,pi,ebb_min, &
5555
real(kind_phys) :: timeq, fire_age, age_hr, dt1,dt2,dtm ! For BB emis. diurnal cycle calculation
5656

5757
! For Gaussian diurnal cycle
58-
real(kind_phys), PARAMETER :: sc_factor=1. ! to scale up the wildfire emissions, TBD later
58+
real(kind_phys), INTENT(IN) :: sc_factor ! to scale up the wildfire emissions
5959
real(kind_phys), PARAMETER :: rinti=2.1813936e-8, ax2=3400., const2=130., &
6060
coef2=10.6712963e-4, cx2=7200., timeq_max=3600.*24.
6161
!>-- Fire parameters: Fores west, Forest east, Shrubland, Savannas, Grassland, Cropland
6262
real(kind_phys), dimension(1:5), parameter :: avg_fire_dur = (/8.9, 4.2, 3.3, 3.0, 1.4/)
6363
real(kind_phys), dimension(1:5), parameter :: sigma_fire_dur = (/8.7, 6.0, 5.5, 5.2, 2.4/)
64+
! For fire diurnal cycle calculation
65+
!real(kind_phys), parameter :: avgx1=-2.0, sigmx1=0.7, C1=0.083 ! Ag fires
66+
!real(kind_phys), parameter :: avgx2=-0.1, sigmx2=0.8, C2=0.55 ! Grass fires, slash burns
67+
real(kind_phys), parameter :: avgx1=0., sigmx1=2.2, C1=0.2 ! Ag fires
68+
real(kind_phys), parameter :: avgx2=0.5, sigmx2=0.8, C2=1.1 ! Grass fires, slash burns
6469

6570
timeq= gmt*3600._kind_phys + real(time_int,4)
6671
timeq= mod(timeq,timeq_max)
@@ -70,34 +75,31 @@ subroutine add_emis_burn(dtstep,dz8w,rho_phy,pi,ebb_min, &
7075

7176
do j=jts,jte
7277
do i=its,ite
73-
fire_age= time_int/3600._kind_phys + (fire_end_hr(i,j)-1._kind_phys) !One hour delay is due to the latency of the RAVE files
74-
fire_age= MAX(0.1_kind_phys,fire_age) ! in hours
78+
fire_age= MAX(0.01_kind_phys,time_int/3600. + (fire_end_hr(i,j)-2.0)) !One hour delay is due to the latency of the RAVE files, hours; one more hour subtracted to have fire_end_hr in the range of 0-24 instead of 0-25
7579

7680
SELECT CASE ( fire_type(i,j) ) !Ag, urban fires, bare land etc.
7781
CASE (1)
7882
! these fires will have exponentially decreasing diurnal cycle,
79-
coef_bb_dc(i,j) = coef_con*1._kind_phys/(sigma_fire_dur(5) *fire_age) * &
80-
exp(- ( log(fire_age) - avg_fire_dur(5))**2 /(2._kind_phys*sigma_fire_dur(5)**2 ))
83+
!coef_bb_dc(i,j) = coef_con*1._kind_phys/(sigma_fire_dur(5) *fire_age) * &
84+
! exp(- ( log(fire_age) - avg_fire_dur(5))**2 /(2._kind_phys*sigma_fire_dur(5)**2 ))
85+
coef_bb_dc(i,j)= C1/(sigmx1* fire_age)* exp(- (log(fire_age) - avgx1)**2 /(2.*sigmx1**2 ) )
8186

8287
IF ( dbg_opt .AND. time_int<5000.) then
8388
WRITE(6,*) 'i,j,peak_hr(i,j) ',i,j,peak_hr(i,j)
8489
WRITE(6,*) 'coef_bb_dc(i,j) ',coef_bb_dc(i,j)
8590
END IF
8691

87-
CASE (2) ! Savanna and grassland fires
88-
coef_bb_dc(i,j) = coef_con*1._kind_phys/(sigma_fire_dur(4) *fire_age) * &
89-
exp(- ( log(fire_age) - avg_fire_dur(4))**2 /(2._kind_phys*sigma_fire_dur(4)**2 ))
92+
CASE (2) ! Savanna and grassland fires, or fires in the eastern US
93+
! coef_bb_dc(i,j) = coef_con*1._kind_phys/(sigma_fire_dur(4) *fire_age) * &
94+
! exp(- ( log(fire_age) - avg_fire_dur(4))**2 /(2._kind_phys*sigma_fire_dur(4)**2 ))
95+
coef_bb_dc(i,j)= C2/(sigmx2* fire_age)* exp(- (log(fire_age) - avgx2)**2 /(2.*sigmx2**2 ) )
9096

9197
IF ( dbg_opt .AND. time_int<5000.) then
9298
WRITE(6,*) 'i,j,peak_hr(i,j) ',i,j,peak_hr(i,j)
9399
WRITE(6,*) 'coef_bb_dc(i,j) ',coef_bb_dc(i,j)
94100
END IF
95101

96-
97-
98-
CASE (3)
99-
!age_hr= fire_age/3600._kind_phys
100-
102+
CASE (3,4) ! wildfires
101103
IF (swdown(i,j)<.1 .AND. fire_age> 12. .AND. fire_hist(i,j)>0.75) THEN
102104
fire_hist(i,j)= 0.75_kind_phys
103105
ENDIF
@@ -113,15 +115,15 @@ subroutine add_emis_burn(dtstep,dz8w,rho_phy,pi,ebb_min, &
113115
dc_hwp= MAX(0._kind_phys,dc_hwp)
114116
dc_hwp= MIN(20._kind_phys,dc_hwp)
115117

116-
! RAR: Gaussian profile for wildfires
117-
dt1= abs(timeq - peak_hr(i,j))
118-
dt2= timeq_max - peak_hr(i,j) + timeq ! peak hour is always <86400.
119-
dtm= MIN(dt1,dt2)
120-
dc_gp = rinti*( ax2 * exp(- dtm**2/(2._kind_phys*cx2**2) ) + const2 - coef2*timeq )
121-
dc_gp = MAX(0._kind_phys,dc_gp)
118+
! RAR: Gaussian profile for wildfires, to be used later
119+
!dt1= abs(timeq - peak_hr(i,j))
120+
!dt2= timeq_max - peak_hr(i,j) + timeq ! peak hour is always <86400.
121+
!dtm= MIN(dt1,dt2)
122+
!dc_gp = rinti*( ax2 * exp(- dtm**2/(2._kind_phys*cx2**2) ) + const2 - coef2*timeq )
123+
!dc_gp = MAX(0._kind_phys,dc_gp)
122124

123125
!dc_fn = MIN(dc_hwp/dc_gp,3._kind_phys)
124-
coef_bb_dc(i,j) = fire_hist(i,j)* dc_hwp
126+
coef_bb_dc(i,j) = sc_factor* fire_hist(i,j)* dc_hwp ! RAR: scaling factor is applied to the forest fires only, except the eastern US
125127

126128
IF ( dbg_opt .AND. time_int<5000.) then
127129
WRITE(6,*) 'i,j,fire_hist(i,j),peak_hr(i,j) ', i,j,fire_hist(i,j),peak_hr(i,j)
@@ -146,7 +148,7 @@ subroutine add_emis_burn(dtstep,dz8w,rho_phy,pi,ebb_min, &
146148
if (ebb_dcycle==1) then
147149
conv= dtstep/(rho_phy(i,k,j)* dz8w(i,k,j))
148150
elseif (ebb_dcycle==2) then
149-
conv= sc_factor*coef_bb_dc(i,j)*dtstep/(rho_phy(i,k,j)* dz8w(i,k,j))
151+
conv= coef_bb_dc(i,j)*dtstep/(rho_phy(i,k,j)* dz8w(i,k,j))
150152
endif
151153
dm_smoke= conv*ebu(i,k,j)
152154
chem(i,k,j,p_smoke) = chem(i,k,j,p_smoke) + dm_smoke

physics/smoke_dust/rrfs_smoke_config.F90

+1
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@ module rrfs_smoke_config
4343
logical :: extended_sd_diags = .false.
4444
real(kind_phys) :: wetdep_ls_alpha = .5 ! scavenging factor
4545
real(kind_phys) :: plume_alpha = 0.05
46+
real(kind_phys) :: sc_factor = 1.0
4647

4748
! --
4849
integer, parameter :: CHEM_OPT_GOCART= 1

physics/smoke_dust/rrfs_smoke_wrapper.F90

+22-12
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,8 @@ module rrfs_smoke_wrapper
1414
num_moist, num_chem, num_emis_seas, num_emis_dust, &
1515
p_qv, p_atm_shum, p_atm_cldq,plume_wind_eff, &
1616
p_smoke, p_dust_1, p_coarse_pm, epsilc, &
17-
n_dbg_lines, add_fire_moist_flux, plume_alpha
17+
n_dbg_lines, add_fire_moist_flux, plume_alpha, &
18+
sc_factor
1819
use dust_data_mod, only : dust_alpha, dust_gamma, dust_moist_opt, &
1920
dust_moist_correction, dust_drylimit_factor
2021
use seas_mod, only : gocart_seasalt_driver
@@ -47,7 +48,8 @@ subroutine rrfs_smoke_wrapper_init( seas_opt_in,
4748
rrfs_sd, do_plumerise_in, plumerisefire_frq_in, & ! smoke namelist
4849
plume_wind_eff_in,add_fire_heat_flux_in, & ! smoke namelist
4950
addsmoke_flag_in, ebb_dcycle_in, hwp_method_in, & ! smoke namelist
50-
add_fire_moist_flux_in, plume_alpha_in, & ! smoke namelist
51+
add_fire_moist_flux_in, & ! smoke namelist
52+
sc_factor_in, plume_alpha_in, & ! smoke namelist
5153
dust_opt_in, dust_alpha_in, dust_gamma_in, & ! dust namelist
5254
dust_moist_opt_in, & ! dust namelist
5355
dust_moist_correction_in, dust_drylimit_factor_in, & ! dust namelist
@@ -59,6 +61,7 @@ subroutine rrfs_smoke_wrapper_init( seas_opt_in,
5961
real(kind_phys), intent(in) :: dust_alpha_in, dust_gamma_in, wetdep_ls_alpha_in, plume_alpha_in
6062
real(kind_phys), intent(in) :: dust_moist_correction_in
6163
real(kind_phys), intent(in) :: dust_drylimit_factor_in
64+
real(kind_phys), intent(in) :: sc_factor_in
6265
integer, intent(in) :: dust_opt_in,dust_moist_opt_in, wetdep_ls_opt_in, pm_settling_in, seas_opt_in
6366
integer, intent(in) :: drydep_opt_in
6467
logical, intent(in) :: aero_ind_fdb_in,dbg_opt_in, extended_sd_diags_in, add_fire_heat_flux_in, add_fire_moist_flux_in
@@ -97,6 +100,7 @@ subroutine rrfs_smoke_wrapper_init( seas_opt_in,
97100
add_fire_heat_flux = add_fire_heat_flux_in
98101
add_fire_moist_flux = add_fire_moist_flux_in
99102
plume_alpha = plume_alpha_in
103+
sc_factor = sc_factor_in
100104
!>-Feedback
101105
aero_ind_fdb = aero_ind_fdb_in
102106
!>-Other
@@ -379,17 +383,18 @@ subroutine rrfs_smoke_wrapper_run(im, flag_init, kte, kme, ktau, dt, garea, land
379383
! cropland, urban, cropland/natural mosaic, barren and sparsely
380384
! vegetated and non-vegetation areas:
381385
lu_qfire(i,j) = lu_nofire(i,j) + vegfrac(i,12,j) + vegfrac(i,13,j) + vegfrac(i,14,j) + vegfrac(i,16,j)
382-
! Savannas and grassland fires, these fires last longer than the Ag
383-
! fires:
384-
lu_sfire(i,j) = lu_nofire(i,j) + vegfrac(i,8,j) + vegfrac(i,9,j) + vegfrac(i,10,j)
386+
! Savannas and grassland fires, these fires last longer than the Ag fires:
387+
lu_sfire(i,j) = lu_qfire(i,j) + vegfrac(i,8,j) + vegfrac(i,9,j) + vegfrac(i,10,j)
385388
if (lu_nofire(i,j)>0.95) then ! no fires
386389
fire_type(i,j) = 0
387390
else if (lu_qfire(i,j)>0.9) then ! Ag. and urban fires
388391
fire_type(i,j) = 1
389-
else if (lu_sfire(i,j)>0.9) then ! savanna and grassland fires
390-
fire_type(i,j) = 2
391-
else
392-
fire_type(i,j) = 3 ! wildfires, new approach is necessary for the controlled burns in the forest areas
392+
else if (xlong(i,j)>260. .AND. xlat(i,j)>25. .AND. xlat(i,j)<41.) then
393+
fire_type(i,j) = 2 ! slash burn and wildfires in the east, eastern temperate forest ecosystem
394+
else if (lu_sfire(i,j)>0.8) then
395+
fire_type(i,j) = 3 ! savanna and grassland fires
396+
else
397+
fire_type(i,j) = 4 ! potential wildfires
393398
end if
394399
end if
395400
end do
@@ -443,7 +448,11 @@ subroutine rrfs_smoke_wrapper_run(im, flag_init, kte, kme, ktau, dt, garea, land
443448
! Apply the diurnal cycle coefficient to frp_inst ()
444449
do j=jts,jte
445450
do i=its,ite
446-
frp_inst(i,j) = MIN(frp_in(i,j)*coef_bb_dc(i,j),frp_max)
451+
IF ( fire_type(i,j) .eq. 4 ) THEN ! only apply scaling factor to wildfires
452+
frp_inst(i,j) = MIN(sc_factor*frp_in(i,j)*coef_bb_dc(i,j),frp_max)
453+
ELSE
454+
frp_inst(i,j) = MIN(frp_in(i,j)*coef_bb_dc(i,j),frp_max)
455+
ENDIF
447456
enddo
448457
enddo
449458

@@ -471,7 +480,8 @@ subroutine rrfs_smoke_wrapper_run(im, flag_init, kte, kme, ktau, dt, garea, land
471480
fire_end_hr, peak_hr,curr_secs, &
472481
coef_bb_dc,fire_hist,hwp_local,hwp_day_avg, &
473482
swdown,ebb_dcycle,ebu_in,ebu,fire_type, &
474-
moist(:,:,:,p_qv), add_fire_moist_flux, &
483+
moist(:,:,:,p_qv), add_fire_moist_flux, &
484+
sc_factor, &
475485
ids,ide, jds,jde, kds,kde, &
476486
ims,ime, jms,jme, kms,kme, &
477487
its,ite, jts,jte, kts,kte , mpiid )
@@ -960,7 +970,7 @@ subroutine rrfs_smoke_prep( &
960970

961971
!---- Calculate HWP based on selected method
962972
hwp_local = 0._kind_phys
963-
precip_factor = 5._kind_phys + real(hour_int)*5._kind_phys/24._kind_phys
973+
precip_factor = 2.5_kind_phys + real(hour_int, kind=kind_phys)*2.5_kind_phys/24._kind_phys
964974
! total precip is only in the SMOKE_RRFS_DATA if ebb_dcycle == 2 and should be
965975
! filled here before calculating HWP
966976
! !!WARNING!! IF EBB_DYCLE != 2 and HWP_METHOD = 1 | 3, HWP will not take into account totprcp_24hrs

physics/smoke_dust/rrfs_smoke_wrapper.meta

+11-3
Original file line numberDiff line numberDiff line change
@@ -93,9 +93,9 @@
9393
type = integer
9494
intent = in
9595
[hwp_method_in]
96-
standard_name = do_smoke_forecast
97-
long_name = index for rrfs smoke forecast
98-
units = index
96+
standard_name = control_for_HWP_equation
97+
long_name = control for HWP equation
98+
units = 1
9999
dimensions = ()
100100
type = integer
101101
intent = in
@@ -106,6 +106,14 @@
106106
dimensions = ()
107107
type = logical
108108
intent = in
109+
[sc_factor_in]
110+
standard_name = scale_factor_for_wildfire_emissions
111+
long_name = scale factor for wildfire emissions
112+
units = 1
113+
dimensions = ()
114+
type = real
115+
kind = kind_phys
116+
intent = in
109117
[plume_alpha_in]
110118
standard_name = alpha_for_plumerise_scheme
111119
long_name = alpha paramter for plumerise scheme

0 commit comments

Comments
 (0)