Skip to content

Commit fb92517

Browse files
authored
Merge pull request #1326 from adrifoster/fire_refactor_lightning
Refactor SPITFIRE - overhaul of fire behavior sections (but bit4bit)
2 parents 6903518 + eb99d91 commit fb92517

File tree

9 files changed

+1312
-302
lines changed

9 files changed

+1312
-302
lines changed

biogeochem/EDPatchDynamicsMod.F90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -434,7 +434,8 @@ subroutine disturbance_rates( site_in, bc_in)
434434
endif
435435

436436
! Fire Disturbance Rate
437-
currentPatch%disturbance_rates(dtype_ifire) = currentPatch%frac_burnt
437+
currentPatch%disturbance_rates(dtype_ifire) = currentPatch%frac_burnt
438+
438439

439440
! Fires can't burn the whole patch, as this causes /0 errors.
440441
if (currentPatch%disturbance_rates(dtype_ifire) > 0.98_r8)then

fire/FatesFuelMod.F90

Lines changed: 96 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,8 @@ module FatesFuelMod
3434
procedure :: UpdateFuelMoisture
3535
procedure :: AverageBulkDensity_NoTrunks
3636
procedure :: AverageSAV_NoTrunks
37+
procedure :: CalculateFuelBurnt
38+
procedure :: CalculateResidenceTime
3739

3840
end type fuel_type
3941

@@ -354,8 +356,8 @@ subroutine AverageSAV_NoTrunks(this, sav_fuel)
354356
! Pyne et al., 1996 (Introduction to wildland fire)
355357

356358
! ARGUMENTS:
357-
class(fuel_type), intent(inout) :: this ! fuel class
358-
real(r8), intent(in) :: sav_fuel(num_fuel_classes) ! surface area to volume ratio of all fuel types [/cm]
359+
class(fuel_type), intent(inout) :: this ! fuel class
360+
real(r8), intent(in) :: sav_fuel(num_fuel_classes) ! surface area to volume ratio of all fuel types [/cm]
359361

360362
! LOCALS:
361363
integer :: i ! looping index
@@ -376,4 +378,96 @@ end subroutine AverageSAV_NoTrunks
376378

377379
!---------------------------------------------------------------------------------------
378380

381+
subroutine CalculateFuelBurnt(this, fuel_consumed)
382+
! DESCRIPTION:
383+
! Calculates the fraction and total amount of fuel burnt
384+
!
385+
386+
use SFParamsMod, only : SF_val_mid_moisture, SF_val_mid_moisture_Coeff
387+
use SFParamsMod, only : SF_val_mid_moisture_Slope, SF_val_min_moisture
388+
use SFParamsMod, only : SF_val_low_moisture_Coeff, SF_val_low_moisture_Slope
389+
use SFParamsMod, only : SF_val_miner_total
390+
391+
! ARGUMENTS:
392+
class(fuel_type), intent(inout) :: this ! fuel class
393+
real(r8), intent(out) :: fuel_consumed(num_fuel_classes) ! fuel consumed [kgC/m2]
394+
395+
! LOCALS:
396+
real(r8) :: rel_moisture ! relative moisture of fuel (moist/moisture of extinction) [unitless]
397+
integer :: i ! looping index
398+
399+
! CONSTANTS:
400+
real(r8), parameter :: max_grass_frac = 0.8_r8 ! maximum fraction burnt for live grass fuels
401+
402+
this%frac_burnt(:) = 1.0_r8
403+
404+
! Calculate fraction of litter is burnt for all classes.
405+
! Equation B1 in Thonicke et al. 2010
406+
do i = 1, num_fuel_classes
407+
408+
rel_moisture = this%effective_moisture(i)
409+
410+
if (rel_moisture <= SF_val_min_moisture(i)) then
411+
! very dry litter
412+
this%frac_burnt(i) = 1.0_r8
413+
else if (rel_moisture > SF_val_min_moisture(i) .and. rel_moisture <= SF_val_mid_moisture(i)) then
414+
! low to medium moisture
415+
this%frac_burnt(i) = max(0.0_r8, min(1.0_r8, SF_val_low_moisture_Coeff(i) - &
416+
SF_val_low_moisture_Slope(i)*rel_moisture))
417+
else if (rel_moisture > SF_val_mid_moisture(i) .and. rel_moisture <= 1.0_r8) then
418+
! medium to high moisture
419+
this%frac_burnt(i) = max(0.0_r8, min(1.0_r8, SF_val_mid_moisture_Coeff(i) - &
420+
SF_val_mid_moisture_Slope(i)*rel_moisture))
421+
else
422+
! very wet litter
423+
this%frac_burnt(i) = 0.0_r8
424+
endif
425+
426+
! we can't ever kill all of the grass
427+
if (i == fuel_classes%live_grass()) then
428+
this%frac_burnt(i) = min(max_grass_frac, this%frac_burnt(i))
429+
end if
430+
431+
! reduce fraction burnt based on mineral content
432+
this%frac_burnt(i) = this%frac_burnt(i)*(1.0_r8 - SF_val_miner_total)
433+
434+
! calculate fuel consumed
435+
fuel_consumed(i) = this%frac_burnt(i)*this%loading(i)
436+
end do
437+
438+
end subroutine CalculateFuelBurnt
439+
440+
!-------------------------------------------------------------------------------------
441+
442+
subroutine CalculateResidenceTime(this, tau_l)
443+
!
444+
! DESCRIPTION:
445+
! Calculates fire residence time, duration of lethal bole heating [min]
446+
! This is used for determining cambial kill of woody cohorts
447+
!
448+
! From Peterson & Ryan (1986)
449+
!
450+
451+
! ARGUMENTS:
452+
class(fuel_type), intent(in) :: this ! fuel class
453+
real(r8), intent(out) :: tau_l ! duration of lethal bole heating [min]
454+
455+
! LOCALS:
456+
integer :: i ! looping index
457+
458+
tau_l = 0.0_r8
459+
do i = 1, num_fuel_classes
460+
if (i /= fuel_classes%trunks()) then
461+
! don't include 1000-hr fuels
462+
! convert loading from kgC/m2 to g/cm2
463+
tau_l = tau_l + 39.4_r8*(this%frac_loading(i)*this%non_trunk_loading/0.45_r8/10.0_r8)* &
464+
(1.0_r8 - ((1.0_r8 - this%frac_burnt(i))**0.5_r8))
465+
end if
466+
end do
467+
468+
! cap the residence time to 8mins, as suggested by literature survey by P&R (1986)
469+
tau_l = min(8.0_r8, tau_l)
470+
471+
end subroutine CalculateResidenceTime
472+
379473
end module FatesFuelMod

fire/SFEquationsMod.F90

Lines changed: 150 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,13 +16,19 @@ module SFEquationsMod
1616
public :: MaximumReactionVelocity
1717
public :: OptimumReactionVelocity
1818
public :: OptimumPackingRatio
19+
public :: MoistureCoefficient
1920
public :: ReactionIntensity
2021
public :: HeatofPreignition
2122
public :: EffectiveHeatingNumber
2223
public :: WindFactor
2324
public :: PropagatingFlux
2425
public :: ForwardRateOfSpread
2526
public :: BackwardRateOfSpread
27+
public :: FireDuration
28+
public :: LengthToBreadth
29+
public :: FireSize
30+
public :: AreaBurnt
31+
public :: FireIntensity
2632

2733
contains
2834

@@ -62,7 +68,11 @@ real(r8) function MaximumReactionVelocity(SAV)
6268
! ARGUMENTS:
6369
real(r8), intent(in) :: SAV ! fuel surface area to volume ratio [/cm]
6470

65-
MaximumReactionVelocity = 1.0_r8/(0.0591_r8 + 2.926_r8*(SAV**(-1.5_r8)))
71+
if (SAV < nearzero) then
72+
MaximumReactionVelocity = 0.0_r8
73+
else
74+
MaximumReactionVelocity = 1.0_r8/(0.0591_r8 + 2.926_r8*(SAV**(-1.5_r8)))
75+
end if
6676

6777
end function MaximumReactionVelocity
6878

@@ -112,6 +122,13 @@ real(r8) function MoistureCoefficient(moisture, MEF)
112122
! LOCALS:
113123
real(r8) :: mw_weight ! relative fuel moisture/fuel moisture of extinction
114124

125+
if (MEF < nearzero) then
126+
! this really should never happen - essentially this means fuel can never burn
127+
! but we are putting this here to avoid divide by zeros
128+
MoistureCoefficient = 0.0_r8
129+
return
130+
end if
131+
115132
! average values for litter pools (dead leaves, twigs, small and large branches), plus grass
116133
mw_weight = moisture/MEF
117134

@@ -314,5 +331,137 @@ real(r8) function BackwardRateOfSpread(ros_front, wind_speed)
314331
end function BackwardRateOfSpread
315332

316333
!-------------------------------------------------------------------------------------
334+
335+
real(r8) function FireDuration(FDI)
336+
!
337+
! DESCRIPTION:
338+
! Calculates fire duration [min]
339+
!
340+
! Equation 14 in Thonicke et al. 2010
341+
!
342+
use SFParamsMod, only : SF_val_max_durat, SF_val_durat_slope
343+
344+
! ARGUMENTS:
345+
real(r8), intent(in) :: FDI ! fire danger index [0-1]
346+
347+
FireDuration = (SF_val_max_durat + 1.0_r8)/(1.0_r8 + SF_val_max_durat* &
348+
exp(SF_val_durat_slope*FDI))
349+
350+
end function FireDuration
351+
352+
!-------------------------------------------------------------------------------------
353+
354+
real(r8) function LengthToBreadth(effective_windspeed, tree_fraction)
355+
!
356+
! DESCRIPTION:
357+
! Calculates length to breadth ratio of fire ellipse [unitless], used for calculating area burnt
358+
!
359+
! Canadian Forest Fire Behavior Prediction System Ont.Int.Rep. ST-X-3, 1992
360+
! Information Report GLC-X-10, Wotten et al. 2009
361+
!
362+
use FatesConstantsMod, only : m_per_km, min_per_hr
363+
364+
! ARGUMENTS:
365+
real(r8), intent(in) :: effective_windspeed ! effective windspeed [m/min]
366+
real(r8), intent(in) :: tree_fraction ! tree fraction [0-1]
367+
368+
! LOCALS:
369+
real(r8) :: windspeed_km_hr ! effective windspeed, converted to correct units [km/hr]
370+
371+
! CONSTANTS:
372+
real(r8), parameter :: lb_threshold = 0.55_r8 ! tree canopy fraction below which to use grassland length-to-breadth eqn
373+
374+
windspeed_km_hr = effective_windspeed/m_per_km*min_per_hr
375+
376+
if (windspeed_km_hr < 1.0_r8) then
377+
LengthToBreadth = 1.0_r8
378+
else
379+
if (tree_fraction > lb_threshold) then
380+
LengthToBreadth = 1.0_r8 + 8.729_r8*((1.0_r8 - exp(-0.03_r8*windspeed_km_hr))**2.155_r8)
381+
else
382+
LengthToBreadth = 1.1_r8*(windspeed_km_hr**0.464_r8)
383+
endif
384+
endif
385+
386+
end function LengthToBreadth
387+
388+
!-------------------------------------------------------------------------------------
389+
390+
real(r8) function FireSize(length_to_breadth, ros_back, ros_forward, fire_duration)
391+
!
392+
! DESCRIPTION:
393+
! Calculates fire size [m2]
394+
!
395+
! Eq 14 Arora and Boer JGR 2005 (area of an ellipse)
396+
!
397+
use FatesConstantsMod, only : pi_const
398+
399+
! ARGUMENTS:
400+
real(r8), intent(in) :: length_to_breadth ! length to breadth ratio of fire ellipse [unitless]
401+
real(r8), intent(in) :: ros_back ! backwards rate of spread [m/min]
402+
real(r8), intent(in) :: ros_forward ! forward rate of spread [m/min]
403+
real(r8), intent(in) :: fire_duration ! fire duration [min]
404+
405+
! LOCALS:
406+
real(r8) :: dist_back ! distance fire has travelled backwards [m]
407+
real(r8) :: dist_forward ! distance fire has travelled forward [m]
408+
real(r8) :: fire_size ! area of fire [m2]
409+
410+
dist_back = ros_back*fire_duration
411+
dist_forward = ros_forward*fire_duration
412+
413+
! Eq 14 Arora and Boer JGR 2005 (area of an ellipse)
414+
if (length_to_breadth < nearzero) then
415+
FireSize = 0.0_r8
416+
else
417+
FireSize = (pi_const/(4.0_r8*length_to_breadth))*((dist_forward + dist_back)**2.0_r8)
418+
end if
419+
420+
end function FireSize
421+
422+
!-------------------------------------------------------------------------------------
423+
424+
real(r8) function AreaBurnt(fire_size, num_ignitions, FDI)
425+
!
426+
! DESCRIPTION:
427+
! Calculates area burnt [m2/km2/day]
428+
!
429+
! daily area burnt = size fires in m2 * num ignitions per day per km2 * prob ignition starts fire
430+
! Thonicke 2010 Eq. 1
431+
!
432+
! the denominator in the units of currentSite%NF is total gridcell area, but since we assume that ignitions
433+
! are equally probable across patches, currentSite%NF is equivalently per area of a given patch
434+
! thus AreaBurnt has units of m2 burned area per km2 patch area per day
435+
!
436+
! TO DO: Connect here with the Li & Levis GDP fire suppression algorithm.
437+
! Equation 16 in arora and boer model JGR 2005
438+
!
439+
440+
! ARGUMENTS:
441+
real(r8), intent(in) :: fire_size ! fire size [m2]
442+
real(r8), intent(in) :: num_ignitions ! number of ignitions [/km2/day]
443+
real(r8), intent(in) :: FDI ! fire danger index [0-1]
444+
445+
AreaBurnt = fire_size*num_ignitions*FDI
446+
447+
end function AreaBurnt
448+
449+
!-------------------------------------------------------------------------------------
450+
451+
real(r8) function FireIntensity(fuel_consumed, ros)
452+
!
453+
! DESCRIPTION:
454+
! Calculates fire intensity [kW/m]
455+
! Eq 15 Thonicke et al 2010
456+
457+
use SFParamsMod, only : SF_val_fuel_energy
458+
459+
! ARGUMENTS:
460+
real(r8), intent(in) :: fuel_consumed ! fuel consumed [kg/m2]
461+
real(r8), intent(in) :: ros ! rate of spread [m/s]
462+
463+
FireIntensity = SF_val_fuel_energy*fuel_consumed*ros
464+
465+
end function FireIntensity
317466

318467
end module SFEquationsMod

0 commit comments

Comments
 (0)