Skip to content

Commit

Permalink
using fire_hfx from file
Browse files Browse the repository at this point in the history
  • Loading branch information
janmandel committed Jul 27, 2012
1 parent 233cc08 commit 479c944
Show file tree
Hide file tree
Showing 3 changed files with 86 additions and 64 deletions.
15 changes: 10 additions & 5 deletions wrfv2_fire/phys/module_fr_sfire_driver.F
Expand Up @@ -334,6 +334,7 @@ subroutine sfire_driver_em ( grid , config_flags &
grid%f_ros0,grid%f_rosx,grid%f_rosy,grid%f_ros,& ! fire risk spread
grid%f_int,grid%f_lineint,grid%f_lineint2, & ! fire risk intensities
grid%fxlong,grid%fxlat, &
grid%fire_hfx, & !
grid%nfuel_cat, & ! input, or internal for safekeeping
grid%fuel_time, &
grid%fz0, grid%fwh, &
Expand Down Expand Up @@ -413,6 +414,7 @@ subroutine sfire_driver_phys (ifun, &
f_ros0,f_rosx,f_rosy,f_ros, & ! fire risk spread
f_int,f_lineint,f_lineint2, & ! fire risk intensities
fxlong,fxlat, & !
fire_hfx, & !
nfuel_cat, & ! in array, data, fire grid, or constant internal
fuel_time, & ! save constant internal data, fire grid
fz0,fwh, &
Expand Down Expand Up @@ -522,7 +524,8 @@ subroutine sfire_driver_phys (ifun, &

! ***** data (constant in time) *****

real, dimension(ifms:ifme, jfms:jfme), intent(inout)::fxlong,fxlat ! fire mesh coordinates
real, dimension(ifms:ifme, jfms:jfme), intent(inout)::fxlong,fxlat, & ! fire mesh coordinates
fire_hfx
real, intent(out), dimension(ifms:ifme, jfms:jfme)::fuel_time ! fire params arrays

type(fire_params),intent(inout)::fp
Expand Down Expand Up @@ -837,7 +840,8 @@ subroutine sfire_driver_phys (ifun, &
dxf,dyf, & ! fire mesh spacing
ignition, & ! description of ignition lines
fxlong,fxlat, & ! fire mesh coordinates
lfn,lfn_out,tign,fuel_frac, & ! state: level function, ign time, fuel left
fire_hfx, & ! given heat flux
lfn,lfn_out,tign,fuel_frac, & ! state: level function, ign time, fuel left
fire_area, & ! output: fraction of cell burning
fgrnhfx,fgrnqfx, & ! output: heat fluxes
ros,flineint,flineint2, & ! diagnostic variables
Expand Down Expand Up @@ -1170,10 +1174,11 @@ subroutine set_flags(config_flags)
fuel_left_method = config_flags%fire_fuel_left_method
fuel_left_irl = config_flags%fire_fuel_left_irl
fuel_left_jrl = config_flags%fire_fuel_left_jrl
fire_const_time = config_flags%fire_const_time
fire_const_grnhfx = config_flags%fire_const_grnhfx
fire_const_grnqfx = config_flags%fire_const_grnqfx
fire_atm_feedback = config_flags%fire_atm_feedback
fire_hfx_given = config_flags%fire_hfx_given
fire_hfx_num_lines = config_flags%fire_hfx_num_lines
fire_hfx_latent_part = config_flags%fire_hfx_latent_part
fire_hfx_value = config_flags%fire_hfx_value
boundary_guard = config_flags%fire_boundary_guard
fire_back_weight = config_flags%fire_back_weight
fire_grows_only = config_flags%fire_grows_only
Expand Down
119 changes: 69 additions & 50 deletions wrfv2_fire/phys/module_fr_sfire_model.F
Expand Up @@ -24,6 +24,7 @@ subroutine sfire_model ( &
fdx,fdy, & ! fire mesh spacing,
ignition, & ! small array of ignition line descriptions
coord_xf,coord_yf, & ! fire mesh coordinates
fire_hfx, & ! input: given heat flux, or set inside
lfn,lfn_out,tign,fuel_frac,fire_area, & ! state: level function, ign time, fuel left, area burning
grnhfx,grnqfx, & ! output: heat fluxes
ros,flineint,flineint2, & ! diagnostic variables
Expand Down Expand Up @@ -93,7 +94,9 @@ subroutine sfire_model ( &
! array data
type(ignition_type), intent(in):: ignition ! descriptions of ignition lines
real, dimension(ifms:ifme, jfms:jfme), intent(in):: &
coord_xf,coord_yf ! node coordinates
coord_xf,coord_yf ! node coordinates
real, dimension(ifms:ifme, jfms:jfme), intent(inout):: &
fire_hfx ! given heat flux

! state
REAL, INTENT(inout), dimension(ifms:ifme,jfms:jfme):: &
Expand Down Expand Up @@ -141,8 +144,8 @@ subroutine sfire_model ( &


! init flags
freeze_fire = fire_const_time > 0.
print *,'ifun=',ifun,' fire_const_time=',fire_const_time,' freeze_fire=',freeze_fire
freeze_fire = fire_hfx_given .ne. 0
print *,'ifun=',ifun,' fire_hfx_given=',fire_hfx_given,' freeze_fire=',freeze_fire

if(ifun.eq.1)then ! do nothing, init pass 1 is outside only
! !$OMP SINGLE
Expand Down Expand Up @@ -359,7 +362,9 @@ subroutine sfire_model ( &
f_int,f_lineint,f_lineint2) ! fire intensities for danger rating


if(.not. freeze_fire)then
select case(fire_hfx_given)

case(0) ! normal

! compute the heat fluxes from the fuel burned
! needs lfn and tign from neighbors so halo must be updated before
Expand Down Expand Up @@ -397,55 +402,69 @@ subroutine sfire_model ( &
fuel_frac_burnt, & !
grnhfx,grnqfx) !out

else
! artificial heat flux given in namelist.input
case (1, 2)
print *,"expecting fire_hfx to be set in WRF, from wrfinput or wrfrst files"

!*******************************************************************
! Ronan you can change this line if you want a different dependence on time
do j=jfts,jfte
do i=ifts,ifte
grnhfx(i,j) = (1. - fire_hfx_latent_part)*fire_hfx(i,j)
grnqfx(i,j) = fire_hfx_latent_part *fire_hfx(i,j)
enddo
enddo

hfrac = exp(-((time_start + dt-fire_const_time)/fire_const_time_sigma)**2)

!*******************************************************************

ghfx = fire_const_grnhfx*hfrac
gqfx = fire_const_grnqfx*hfrac

!$OMP CRITICAL(SFIRE_MODEL_CRIT)
write(msg,'(a,2e12.3,a,e12.3,a)')'sfire_model: given heat flux', &
ghfx, gqfx, ' W/m^2 '
call message(msg)
write(msg,'(e12.3,a,2e12.3)')hfrac,' of max ',fire_const_grnhfx,fire_const_grnqfx
call message(msg)
!$OMP END CRITICAL(SFIRE_MODEL_CRIT)

! position of the circular fire
sx = fire_const_x
sy = fire_const_y
ex = fire_const_x
ey = fire_const_y
! values to interpolate between (sx,sy), (ex,ey)
st = 0. ! unused
ey = 0. ! unused
cx2=ignition%unit_fxlong**2 ! units of grid cell squared to measure distances
cy2=ignition%unit_fxlat **2

do j=jfts,jfte
do i=ifts,ifte
ax=coord_xf(i,j)
ay=coord_yf(i,j)
! compute d = distance from the line (sx,sy) to (ex,ey)
call nearest(d,tdummy,ax,ay,sx,sy,st,ex,ey,et,cx2,cy2) ! output t unused
if( d < fire_const_r) then
fire_area(i,j) = 1.
else
fire_area(i,j) = 0.
endif
grnhfx(i,j)=ghfx*fire_area(i,j)
grnqfx(i,j)=gqfx*fire_area(i,j)
enddo
enddo
case (3)

print *,"artificial heat flux from parameters given in namelist.input"
call crash('under construction')

endif
! !*******************************************************************
! ! Ronan you can change this line if you want a different dependence on time
!
! hfrac = exp(-((time_start + dt-fire_const_time)/fire_const_time_sigma)**2)
!
! !*******************************************************************
!
! ghfx = fire_const_grnhfx*hfrac
! gqfx = fire_const_grnqfx*hfrac
!
!!$OMP CRITICAL(SFIRE_MODEL_CRIT)
! write(msg,'(a,2e12.3,a,e12.3,a)')'sfire_model: given heat flux', &
! ghfx, gqfx, ' W/m^2 '
! call message(msg)
! write(msg,'(e12.3,a,2e12.3)')hfrac,' of max ',fire_const_grnhfx,fire_const_grnqfx
! call message(msg)
!!$OMP END CRITICAL(SFIRE_MODEL_CRIT)
!
! ! position of the circular fire
! sx = fire_const_x
! sy = fire_const_y
! ex = fire_const_x
! ey = fire_const_y
! ! values to interpolate between (sx,sy), (ex,ey)
! st = 0. ! unused
! ey = 0. ! unused
! cx2=ignition%unit_fxlong**2 ! units of grid cell squared to measure distances
! cy2=ignition%unit_fxlat **2
!
! do j=jfts,jfte
! do i=ifts,ifte
! ax=coord_xf(i,j)
! ay=coord_yf(i,j)
! ! compute d = distance from the line (sx,sy) to (ex,ey)
! call nearest(d,tdummy,ax,ay,sx,sy,st,ex,ey,et,cx2,cy2) ! output t unused
! if( d < fire_const_r) then
! fire_area(i,j) = 1.
! else
! fire_area(i,j) = 0.
! endif
! grnhfx(i,j)=ghfx*fire_area(i,j)
! grnqfx(i,j)=gqfx*fire_area(i,j)
! enddo
! enddo
!
case default
call crash('bad fire_hfx_given')
end select

! this should run in any case

Expand Down
16 changes: 7 additions & 9 deletions wrfv2_fire/phys/module_fr_sfire_util.F
Expand Up @@ -39,22 +39,20 @@ module module_fr_sfire_util
fire_advection=0, & ! 0 = fire spread from normal wind/slope (CAWFE), 1 = full speed projected
fire_wind_log_interp=4,& ! kind of vertical log layer wind interpolation, see driver
fire_use_windrf=0, & ! if fire_wind_log_interp.ne.4: 0=ignore wind reduction factors, 1=multiply, 2=use to set fwh
fire_fmc_read=1 ! fuel moisture: 0 from wrfinput, 1 from namelist.fire, 2 read from file in ideal
fire_fmc_read=1, & ! fuel moisture: 0 from wrfinput, 1 from namelist.fire, 2 read from file in ideal
fire_hfx_given=0, & ! "0=no, run normally, 1=from wrfinput, 2=from file input_hfx in ideal, 4=by parameters" ""
fire_hfx_num_lines=1 ! number of heatflux parameter sets defining the heaflux lines (must be 1)


real, save:: &
fire_perimeter_time=0.,& ! if >0, set lfn from tign until this time, and read tign in ideal
fire_const_time=10., & ! if >0, time from simulation start to the max of gaussian artificial fire (s)
fire_const_time_sigma=5., & ! stdev width of the gaussina impulse (s)
fire_const_x=500., & ! position of the circular fire (m or lon/lat)
fire_const_y=500., & ! position of the circular fire (m or lon/lat)
fire_const_r=500., & ! position of the circular fire (m or lon/lat)
fire_const_grnhfx=1e6, & ! the heat flux at time fire_const_time (W/m^2)
fire_const_grnqfx=1e6, & ! the moisture flux at fire_const_time (W/m^2)
fire_atm_feedback=1. , & ! 1 = normal, 0. = one way coupling atmosphere -> fire only
fire_back_weight=0.5, & ! RK parameter, 0 = Euler method, 0.5 = Heun, 1 = fake backward Euler
fire_viscosity=0.4, & ! artificial viscosity
fire_lfn_ext_up=1. ! 0.=extend level set function at boundary by reflection, 1.=always up
fire_lfn_ext_up=1, & ! 0.=extend level set function at boundary by reflection, 1.=always up
fire_hfx_value=0., & ! heat flux value specified when given by parameterst flux value specified when given by parameters:w
fire_hfx_latent_part=0.084 ! proportion of the given heat flux released as latent, the rest is sensible


integer, parameter:: REAL_SUM=10, REAL_MAX=20, RNRM_SUM=30, RNRM_MAX=40

Expand Down

0 comments on commit 479c944

Please sign in to comment.