Skip to content

Commit

Permalink
connecting the moisture model subroutines through the driver to WRF
Browse files Browse the repository at this point in the history
  • Loading branch information
janmandel committed Feb 25, 2012
1 parent fa7d4b9 commit 6124178
Show file tree
Hide file tree
Showing 4 changed files with 147 additions and 41 deletions.
9 changes: 5 additions & 4 deletions wrfv2_fire/Registry/registry.fire
Expand Up @@ -49,15 +49,18 @@ state real fgrnqfx *i*j fire 1 z hr "FGRNQFX"
state real fcanhfx *i*j fire 1 z hr "FCANHFX" "heat flux from crown fire" "W/m^2"
state real fcanqfx *i*j fire 1 z hr "FCANQFX" "moisture flux from crown fire" "W/m^2"

# fuel moisture model variables
# fuel moisture model section
dimspec num_fmc - namelist=nfmc c fuel_moisture_classes
rconfig integer nfmc namelist,fire 1 5 - "nfmc" "number of fuel moisture classes"
state real fmc_gc i{num_fmc}j fire 1 z hr "FMC_GC" "fuel moisture contents by class" "1"
state real rain_old ij fire 1 z hr "RAIN_OLD" "previous value of accumulated rain" "mm"
state real t2_old ij fire 1 z hr "T2_OLD" "previous value of accumulated rain" "mm"
state real q2_old ij fire 1 z hr "Q2_OLD" "previous value of accumulated rain" "mm"
state real psfc_old ij fire 1 z hr "PSFC_OLD" "previous value of accumulated rain" "mm"
rconfig integer fuel_moisture_steps namelist,fire max_domains 0 - "fuel_moisture_steps" "0=moisture model off, >0 run moisture model every x timesteps"
rconfig logical initialize_fmc namelist,fire 1 .true. hr "initialize_fmc" "set initial moisture to fuelmc_g from namelist.fire"
rconfig logical dynamic_fuel_moisture namelist,fire 1 .true. hr "run fuel moisture model or not"
halo HALO_FIRE_MOIST_FIREGRID dyn_em 24:fmc_g
halo HALO_FIRE_MOIST_ATMGRID dyn_em 8:fmc_gc

# diagnostics
# for the actual modeled fire
Expand Down Expand Up @@ -240,8 +243,6 @@ halo HALO_FIRE_LONGLAT dyn_em 24:xlong,xlat
halo HALO_FIRE_WIND_A dyn_em 8:u_2,v_2
halo HALO_FIRE_ZSF dyn_em 24:zsf
halo HALO_FIRE_FUEL dyn_em 8:fuel_frac,fuel_time,bbb,phiwc,phisc,r_0,fgip,ischap,nfuel_cat,dzdxf,dzdyf,fz0,fwh
halo HALO_FIRE_MOISTURE_FIREGRID dyn_em 8:fmc_g
halo HALO_FIRE_MOISTURE_ATMGRID dyn_em 8:fmc_gc
#
# ----------------------------------------
# end fire variables and configuration
Expand Down
121 changes: 110 additions & 11 deletions wrfv2_fire/phys/module_fr_sfire_driver.F
Expand Up @@ -69,7 +69,7 @@ module module_fr_sfire_driver
! use this module for standalone call, you only need to provide some mock-up wrf modules

use module_fr_sfire_model, only: sfire_model
use module_fr_sfire_phys, only: fire_params, init_fuel_cats, set_fp_from_grid
use module_fr_sfire_phys, only: fire_params, init_fuel_cats, set_fp_from_grid, fuel_moisture, advance_moisture, init_fuel_cats
use module_fr_sfire_atm, only: apply_windrf,interpolate_wind2fire_height,interpolate_atm2fire, &
interpolate_z2fire,setup_wind_log_interpolation
use module_fr_sfire_util
Expand Down Expand Up @@ -134,6 +134,10 @@ subroutine sfire_driver_em ( grid , config_flags &
character(len=128)msg
type(fire_params)::fp

logical:: run_moisture
real:: dt_moisture



!*** executable

Expand All @@ -145,6 +149,7 @@ subroutine sfire_driver_em ( grid , config_flags &

call set_fp_from_grid(grid,fp)

! **** THE FOLLOWING REALLY SHOULD BE DONE ONCE NOT EVERY TIMESTEP
! get ignition data
call fire_ignition_convert (config_flags,ignition)

Expand All @@ -156,8 +161,11 @@ subroutine sfire_driver_em ( grid , config_flags &
jr=grid%sr_y
itimestep=grid%itimestep
restart=config_flags%restart .or. config_flags%cycling .or. config_flags%fire_restart ! skip state initialization


! **** moisture model
! run moisture model this timestep?
run_moisture = .true. .or. config_flags%dynamic_fuel_moisture
dt_moisture = dt ! Time since moisture model run the last time. Should be long. ********* REPLACE *********

!$OMP CRITICAL(SFIRE_DRIVER_CRIT)
write(msg,'(a,i1,a,i1,a,l1)') &
Expand All @@ -172,14 +180,16 @@ subroutine sfire_driver_em ( grid , config_flags &

! 1 = initialize run pass 1: interpolate height to zsf=terrain
! 2 = initialize run pass 2: set fuel data, terrain gradient
! 3 = initialize timestep: interpolate winds, check for ignition
! 4 = do one timestep
! 3 = initialize timestep: interpolate winds, check for ignition, time step on moisture model
! 4 = do one timestep
! 5 = copy timestep output to input
! 6 = compute output fluxes

#ifdef DM_PARALLEL

if(fire_ifun.eq.1)then

call init_fuel_cats ! also initializes the variables for the moisture model
! halo exchange on topography
#include "HALO_FIRE_LONGLAT.inc"
!! if(fire_topo_from_atm.eq.1)then
Expand All @@ -202,6 +212,11 @@ subroutine sfire_driver_em ( grid , config_flags &
! halo exchange on fire winds width 2 for a 2-step RK method
#include "HALO_FIRE_WIND_F.inc"

if(run_moisture)then
! have interpolated to the fire grid, update coefficients
#include "HALO_FIRE_MOIST_FIREGRID.inc"
endif

elseif(fire_ifun.eq.6)then
! computing fuel_left needs ignition time from neighbors
#include "HALO_FIRE_TIGN.inc"
Expand Down Expand Up @@ -248,8 +263,17 @@ subroutine sfire_driver_em ( grid , config_flags &
grid%nfuel_cat, & ! input, or internal for safekeeping
grid%fuel_time, &
grid%fz0, grid%fwh, &
fp &
)
fp, & ! structure with pointers passed to spread rate calculation
config_flags%nfmc, & ! moisture model variables start
config_flags%initialize_fmc, &
run_moisture,dt_moisture, & ! moisture model control
grid%rainc, grid%rainnc, & ! accumulated rain from different sources
grid%t2, grid%q2, grid%psfc, & ! temperature (K), vapor contents (kg/kg), pressure (Pa) at the surface
grid%rain_old, & ! previous value of accumulated rain
grid%t2_old, grid%q2_old, grid%psfc_old, & ! previous values of the atmospheric state at surface
grid%fmc_gc, & ! fuel moisture fields updated, by class, assumed set to something reasonable
fp%fmc_g ) ! write-only alias. need to exit before using fp again


#ifdef DM_PARALLEL
if(fire_ifun.eq.2)then
Expand All @@ -258,6 +282,11 @@ subroutine sfire_driver_em ( grid , config_flags &
! fire state was initialized
call message('halo exchange on lfn width 2')
#include "HALO_FIRE_LFN.inc"
elseif(fire_ifun.eq.3)then
if(run_moisture)then
! moisture model has advanced, prepare for interpolation to the fire grid
#include "HALO_FIRE_MOIST_ATMGRID.inc"
endif
endif
#endif

Expand All @@ -274,7 +303,6 @@ end subroutine sfire_driver_em
!*******************
!

! module_fr_sfire_driver%%sfire_driver
subroutine sfire_driver_phys (ifun, &
ids,ide, kds,kde, jds,jde, & ! atm grid dimensions
ims,ime, kms,kme, jms,jme, &
Expand Down Expand Up @@ -307,8 +335,17 @@ subroutine sfire_driver_phys (ifun, &
nfuel_cat, & ! in array, data, fire grid, or constant internal
fuel_time, & ! save constant internal data, fire grid
fz0,fwh, &
fp & ! fire params
)
fp, & ! fire params
nfmc, & ! number of fuel moisture classes
initialize_fmc, &
run_moisture,dt_moisture, & ! moisture model control
rainc,rainnc, & ! accumulated rain from different sources
t2, q2, psfc, & ! temperature (K), vapor contents (kg/kg), pressure (Pa) at the surface
rain_old, & ! previous value of accumulated rain
t2_old, q2_old, psfc_old, & ! previous values of the atmospheric state at surface
fmc_gc, & ! fuel moisture fields updated, by class, assumed set to something reasonable
fmc_g) ! fuel moisture, alias of fp%fmc_g


implicit none

Expand All @@ -322,6 +359,7 @@ subroutine sfire_driver_phys (ifun, &
ifms, ifme, jfms, jfme, & ! fire memory bounds
ifps, ifpe, jfps, jfpe, & ! fire patch bounds
ir,jr, & ! atm/fire grid refinement ratio
nfmc, & ! number of fuel moisture classes
itimestep, & ! number of this timestep
ifuelread, & ! how to initialize nfuel_cat:
! -1=not at all, done outside
Expand All @@ -333,8 +371,6 @@ subroutine sfire_driver_phys (ifun, &

logical, intent(in)::restart



integer,dimension(num_tiles),intent(in) :: i_start,i_end,j_start,j_end ! atm grid tiling

real, intent(in):: &
Expand Down Expand Up @@ -386,6 +422,17 @@ 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


! moisture model arguments
logical, intent(in)::initialize_fmc,run_moisture
real, intent(in)::dt_moisture
real, intent(in), dimension(ims:ime,jms:jme):: t2, q2, psfc, rainc, rainnc
real, intent(inout), dimension(ims:ime,jms:jme):: t2_old, q2_old, psfc_old, rain_old
real, intent(inout), dimension(ims:ime,nfmc,jms:jme):: fmc_gc
real, intent(inout), dimension(ifms:ifme,jfms:jfme):: fmc_g



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

real, dimension(ifms:ifme, jfms:jfme), intent(inout)::fxlong,fxlat ! fire mesh coordinates
Expand Down Expand Up @@ -590,6 +637,21 @@ subroutine sfire_driver_phys (ifun, &
! after the loop where zsf created exited and all synced
call print_2d_stats(ifts,ifte,jfts,jfte,ifms,ifme,jfms,jfme,fp%zsf,'driver_phys:zsf')

! initialize the moisture model
call advance_moisture( &
.true., & ! initialize timestepping
initialize_fmc, & ! if true, set initial moisture to fuelmc_g
ims,ime, jms,jme, & ! memory dimensions
its,ite, jts,jte, & ! tile dimensions
nfmc, & ! number of moisture fields
dt_moisture, & ! moisture model time step
rainc, rainnc, & ! accumulated rain
t2, q2, psfc, & ! temperature (K), vapor contents (kg/kg), pressure (Pa) at the surface
rain_old, & ! previous value of accumulated rain
t2_old, q2_old, psfc_old, & ! previous values of the atmospheric state at surface
fmc_gc & ! fuel moisture fields updated, by class, assumed set to something reasonable
)

elseif(ifun.eq.3)then ! interpolate winds to the fire grid

if(use_atm_vars)then
Expand Down Expand Up @@ -652,6 +714,43 @@ subroutine sfire_driver_phys (ifun, &


endif

! still with ifun=3

! one timestep of the moisture model
call advance_moisture( &
.false., &
.false., &
ims,ime, jms,jme, & ! memory dimensions
its,ite, jts,jte, & ! tile dimensions
nfmc, & ! number of moisture fields
dt_moisture, & ! moisture model time step
rainc, rainnc, & ! accumulated rain
t2, q2, psfc, & ! temperature (K), vapor contents (kg/kg), pressure (Pa) at the surface
rain_old, & ! previous value of accumulated rain
t2_old, q2_old, psfc_old, & ! previous values of the atmospheric state at surface
fmc_gc & ! fuel moisture fields updated, by class, assumed set to something reasonable
)

elseif(ifun.eq.4)then

! interpolate and compute weighted average to get the fuel moisture
call fuel_moisture( &
id, & ! for prints and maybe file names
nfmc, &
ids,ide, jds,jde, & ! atm grid dimensions
ims,ime, jms,jme, &
ips,ipe,jps,jpe, &
its,ite,jts,jte, &
ifds, ifde, jfds, jfde, & ! fire grid dimensions
ifms, ifme, jfms, jfme, &
ifts,ifte,jfts,jfte, &
ir,jr, & ! atm/fire grid ratio
nfuel_cat, & ! fuel data
fmc_gc, & ! moisture contents by class on atmospheric grid
fmc_g & ! weighted fuel moisture contents on fire grid
)

endif

! the following executes in any case
Expand Down
7 changes: 4 additions & 3 deletions wrfv2_fire/phys/module_fr_sfire_model.F
Expand Up @@ -143,9 +143,10 @@ subroutine sfire_model ( &
freeze_fire = fire_const_time > 0. .and. time_start < fire_const_time

if(ifun.eq.1)then ! do nothing, init pass 1 is outside only
!$OMP SINGLE
call init_fuel_cats ! initialize fuel subsystem
!$OMP END SINGLE
! !$OMP SINGLE
!! done in driver now
! call init_fuel_cats ! initialize fuel subsystem
! !$OMP END SINGLE
elseif(ifun.eq.2)then
! initialize all arrays that the model will not change later

Expand Down
51 changes: 28 additions & 23 deletions wrfv2_fire/phys/module_fr_sfire_phys.F
Expand Up @@ -26,7 +26,7 @@ module module_fr_sfire_phys

! subroutenes and functions
PUBLIC:: init_fuel_cats,fire_ros,heat_fluxes,set_nfuel_cat,set_fire_params, &
write_fuels_m,fire_risk,fire_intensity,set_fp_from_grid
write_fuels_m,fire_risk,fire_intensity,set_fp_from_grid, fuel_moisture,advance_moisture

! types
public:: fire_params
Expand Down Expand Up @@ -281,13 +281,14 @@ subroutine fuel_moisture( &

end subroutine fuel_moisture


subroutine advance_moisture( &
initialize, & ! 0 = run, 1 = initialize previous values, 2 = initialize also moisture
fmc_gc_init, & ! initial value of moisture
ims,ime, jms,jme, & ! memory dimensions
its,ite, jts,jte, & ! tile dimensions
initialize, & ! initialize timestepping
initialize_fmc, &
ims,ime, jms,jme, & ! memory dimensions
its,ite, jts,jte, & ! tile dimensions
nfmc, & ! number of moisture fields
timestep, & ! moisture model time step
moisture_dt, & ! timestep = time step time elapsed from the last call
rainc, rainnc, & ! accumulated rain
t2, q2, psfc, & ! temperature (K), vapor contents (kg/kg), pressure (Pa) at the surface
rain_old, & ! previous value of accumulated rain
Expand All @@ -296,24 +297,38 @@ subroutine advance_moisture( &
)

!*** arguments
logical, intent(in):: initialize,initialize_fmc
integer, intent(in):: &
initialize, & ! 0 = run, other = initialize
ims,ime, jms,jme, & ! memory dimensions
its,ite, jts,jte, & ! tile dimensions
nfmc ! number of moisture fields
real, intent(in):: fmc_gc_init,timestep
real, intent(in):: moisture_dt
real, intent(in), dimension(ims:ime,jms:jme):: t2, q2, psfc, rainc, rainnc
real, intent(inout), dimension(ims:ime,jms:jme):: t2_old, q2_old, psfc_old, rain_old
real, intent(inout), dimension(ims:ime,nfmc,jms:jme):: fmc_gc

!*** module variables
! fuelmc_g

!*** local
integer:: i,j,k
real::rain_int, T, P, Q, QRS, ES, RH, tend, EMC_d, EMC_w, EMC, R, rain_diff, fmc

!*** executable

if(initialize.ge.1)call copy2old
if(initialize.ge.2)call init_fmc_gc
if(initialize)then
call copy2old
if(initialize_fmc)then
do j=jts,jte
do k=1,nfmc
do i=its,ite
fmc_gc(i,k,j)=fuelmc_g ! from module
enddo
enddo
enddo
endif
return
endif

do j=jts,jte
do k=1,nfmc
Expand All @@ -322,7 +337,7 @@ subroutine advance_moisture( &
fmc = fmc_gc(i,k,j)
! compute the rain intensity from the difference of accumulated rain
rain_diff = ((rainc(i,j) + rainnc(i,j)) - rain_old(i,j))
rain_int = rain_diff/timestep
rain_int = rain_diff / moisture_dt
R = rain_int - rain_threshold(k)
if (R > 0.) then
select case(wetting_model(k))
Expand Down Expand Up @@ -351,12 +366,13 @@ subroutine advance_moisture( &
endif
end select
endif
fmc_gc(i,k,j) = fmc + timestep*tend
fmc_gc(i,k,j) = fmc + moisture_dt * tend
enddo
enddo
enddo

call copy2old

return

contains
Expand All @@ -374,17 +390,6 @@ subroutine copy2old

end subroutine copy2old

subroutine init_fmc_gc
do j=jts,jte
do k=1,nfmc
do i=its,ite
fmc_gc(i,k,j)=fmc_gc_init
enddo
enddo
enddo
end subroutine init_fmc_gc


end subroutine advance_moisture


Expand Down

0 comments on commit 6124178

Please sign in to comment.