Skip to content

Commit

Permalink
Changes made in the submitted files at NCAR before the 3.3 release
Browse files Browse the repository at this point in the history
  • Loading branch information
janmandel committed Apr 12, 2011
1 parent 3f78267 commit 9a4e383
Show file tree
Hide file tree
Showing 14 changed files with 651 additions and 209 deletions.
9 changes: 2 additions & 7 deletions wrfv2_fire/phys/module_fr_sfire_atm.F
@@ -1,8 +1,4 @@
!WRF:MEDIATION_LAYER:FIRE_MODEL

!*** Jan Mandel August 2007 - February 2008
!*** email: jmandel@ucar.edu or Jan.Mandel@gmail.com or Jan.Mandel@cudenver.edu

! Routines dealing with the atmosphere

module module_fr_sfire_atm
Expand All @@ -22,9 +18,8 @@ SUBROUTINE fire_tendency( &
rthfrten,rqvfrten) ! theta and Qv tendencies

! This routine is atmospheric physics
! it does NOT go into module_fr_sfire_phys because it is not fire physics
! it does NOT go into module_fr_sfire_phys because it is not related to fire physical processes

! taken from the code by Ned Patton, only order of arguments change to the convention here
! --- this routine takes fire generated heat and moisture fluxes and
! calculates their influence on the theta and water vapor
! --- note that these tendencies are valid at the Arakawa-A location
Expand All @@ -46,7 +41,7 @@ SUBROUTINE fire_tendency( &
REAL, INTENT(in), DIMENSION( ims:ime,kms:kme,jms:jme ) :: dz8w ! dz across w-lvl
REAL, INTENT(in), DIMENSION( ims:ime,kms:kme,jms:jme ) :: rho ! density

REAL, INTENT(in) :: alfg ! extinction depth ground fire heat (m)
REAL, INTENT(in) :: alfg ! extinction depth surface fire heat (m)
REAL, INTENT(in) :: alfc ! extinction depth crown fire heat (m)
REAL, INTENT(in) :: z1can ! height of crown fire heat release (m)

Expand Down
24 changes: 9 additions & 15 deletions wrfv2_fire/phys/module_fr_sfire_core.F
@@ -1,15 +1,12 @@
!
!*** Jan Mandel August-October 2007 email: jmandel@ucar.edu or Jan.Mandel@gmail.com
!
! With contributions by Minjeong Kim.
#define DEBUG_OUT
#define DEBUG_PRINT
!#define FUEL_LEFT
!#define DEBUG_OUT_FUEL_LEFT

module module_fr_sfire_core

use module_fr_sfire_phys
use module_fr_sfire_phys, only: fire_params , fire_ros
use module_fr_sfire_util

! The mathematical core of the fire spread model. No physical constants here.
Expand Down Expand Up @@ -355,8 +352,6 @@ subroutine fuel_left(&
!*** purpose: determine fraction of fuel remaining
!*** NOTE: because variables are cell centered, need halo/sync width 1 before

!*** Jan Mandel August 2007 email: jmandel@ucar.edu or Jan.Mandel@gmail.com

!*** arguments

integer, intent(in) :: its,ite,jts,jte,ims,ime,jms,jme,ifs,ife,jfs,jfe
Expand Down Expand Up @@ -1292,8 +1287,6 @@ subroutine prop_ls( id, & ! for debug

!*** purpose: advance level function in time

! Jan Mandel August 2007 - February 2008

!*** description
!
! Propagation of closed curve by a level function method. The level function
Expand Down Expand Up @@ -1657,7 +1650,8 @@ subroutine tend_ls( id, &
!*** local
real:: te,diffLx,diffLy,diffRx,diffRy, &
diffCx,diffCy,diff2x,diff2y,grad,rr, &
ros_back,ros_wind,ros_slope,advx,advy,scale,nvx,nvy,speed,tanphi
ros_base,ros_wind,ros_slope,ros_back,advx,advy,scale,nvx,nvy, &
speed,tanphi
integer::i,j,itso,iteo,jtso,jteo
character(len=128)msg

Expand Down Expand Up @@ -1743,10 +1737,10 @@ subroutine tend_ls( id, &

! get rate of spread from wind speed and slope

call fire_ros(ros_back,ros_wind,ros_slope, &
call fire_ros(ros_base,ros_wind,ros_slope, &
nvx,nvy,i,j,fp)

rr=ros_back + ros_wind + ros_slope
rr=ros_base + ros_wind + ros_slope
if(fire_grows_only.gt.0)rr=max(rr,0.)

! set ros for output
Expand All @@ -1760,7 +1754,7 @@ subroutine tend_ls( id, &
else

! normal direction backing rate only
te = - ros_back*grad
te = - ros_base*grad

! advection in wind direction
if (abs(speed)> eps) then
Expand Down Expand Up @@ -1923,7 +1917,7 @@ real function speed_func(diffCx,diffCy,dx,dy,i,j,fp)
type(fire_params),intent(in)::fp
!*** local
real::scale,nvx,nvy,r
real::ros_back , ros_wind , ros_slope
real::ros_base , ros_wind , ros_slope
real, parameter:: eps=epsilon(0.0)
!*** executable
! normal direction, from central differences
Expand All @@ -1933,10 +1927,10 @@ real function speed_func(diffCx,diffCy,dx,dy,i,j,fp)

! get rate of spread from wind speed and slope

call fire_ros(ros_back,ros_wind,ros_slope, &
call fire_ros(ros_base,ros_wind,ros_slope, &
nvx,nvy,i,j,fp)

r=ros_back + ros_wind + ros_slope
r=ros_base + ros_wind + ros_slope
if(fire_grows_only.gt.0)r=max(r,0.)
speed_func=r

Expand Down
106 changes: 27 additions & 79 deletions wrfv2_fire/phys/module_fr_sfire_driver.F
@@ -1,73 +1,23 @@
! SFIRE - Spread fire model in WRF-Fire
!
!*** Jan Mandel August 2007 - July 2010
!*** email: Jan.Mandel@gmail.com

! For support please subscribe to the wrf-fire mailing list at NCAR at
! http://mailman.ucar.edu/mailman/listinfo/wrf-fire
! or go to http://www.openwfm.org/wiki/WRF-Fire_user_support

! This module is the only entry point from WRF-ARW to the wildland
! fire model. The call to sfire_driver advances the fire model by
! one timestep. The fire model inputs the wind and outputs
! temperature and humidity tendencies. The fire model also inputs a
! This module is the entry point from WRF ARW to the wildland
! fire module. The call to sfire_driver advances the fire module by
! one timestep. The fire module inputs the wind and outputs
! temperature and humidity tendencies. The fire module also inputs a
! number of constant arrays (fuel data, topography). Additional
! arguments are model state (for data assimilation) and constant arrays
! the model gives to WRF for safekeeping because it is not allowed
! to save anything.

! This code is described in [1]. The fire model is coupled with WRF
! but the fire code itself is not dependent on WRF in any way other
! than calls to few WRF utilities from module_fr_sfire_util. This
! model uses a level set function method for advancing the fireline.
! It is a reimplementation of an earlier model, which used fireline
! propagation by tracers and was coupled with the Clark-Hall
! atmospheric code, described in [2]. For WRF documentation see [3].

! If you use this code, please acknowledge our work by citing [1].
! Thank you.

! Acknowledgements
!
! Contributions to development of the level set
! method by Mijeong Kim. Contribution to fuel calculation by Volodymyr
! Kondratenko.
! Contributions to this wildland fire module have come from individuals at
! NCAR, the U.S.D.A. Forest Service, the Australian Bureau of Meteorology,
! and the University of Colorado at Denver.
!
! The fire physics is adapted from an earlier code by Terry
! L. Clark, Janice L. Coen, and Don Latham [2]. The interface with
! WRF is adapted from a code by Ned Patton for coupling of the earlier
! fire model with WRF, based on the foundation outlined in [4].
! The changes in WRF infrastructure and support of
! refined fire grids were provided by John Michalakes.

! Jonathan D. Beezley has set up and maintained the WRF build and
! execution environment, provided software engineering infrastructure
! including synchronization with the WRF repository, and was responsibe
! for all aspects of WRF modification.

! Refefences
!
! [1] Jan Mandel, Jonathan D. Beezley, Janice L. Coen, and Minjeong Kim,
! Data Asimilation for Wildland Fires: Ensemble Kalman filters in
! coupled atmosphere-surface models, IEEE Control Systems Magazine 29,
! Issue 3, June 2009, 47-65.

! [2] T. L. Clark, J. Coen, and D. Latham, Description of a coupled
! atmosphere-fire model, Intl. J. Wildland Fire, vol. 13, pp. 49-64,
! 2004
!
! [3] http://www.mmm.ucar.edu/wrf/OnLineTutorial/Introduction/index.html
!
! [4] Edward G. Patton and Janice L. Coen, WRF-Fire: A Coupled
! Atmosphere-Fire Module for WRF, Preprints of Joint MM5/Weather
! Research and Forecasting Model Users' Workshop, Boulder, CO,
! June 22-25, 2004, pp. 221-223, NCAR

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
use module_fr_sfire_phys
use module_fr_sfire_phys, only : fire_params , init_fuel_cats
use module_fr_sfire_util
use module_fr_sfire_core, only: ignition_line_type

Expand Down Expand Up @@ -102,7 +52,9 @@ subroutine sfire_driver_em ( grid , config_flags &
! Driver layer modules
#ifdef DM_PARALLEL
USE module_dm , ONLY : ntasks_x,ntasks_y,local_communicator,mytask,ntasks
USE module_comm_dm
USE module_comm_dm , ONLY : halo_fire_fuel_sub, halo_fire_tign_sub, halo_fire_wind_f_sub, &
halo_fire_wind_a_sub, halo_fire_ph_sub, halo_fire_zsf_sub, halo_fire_longlat_sub, &
halo_fire_phb_sub, halo_fire_z0_sub, halo_fire_lfn_sub
#endif

implicit none
Expand Down Expand Up @@ -133,22 +85,20 @@ subroutine sfire_driver_em ( grid , config_flags &

!*** executable

if(fire_ifun_start.le.1)call print_id ! print id only once, during initialization
! populate our structures from wrf

! pointers to be passed to fire spread formulas
fp%vx => grid%uf ! fire winds
fp%vy => grid%vf ! fire winds
! pointers to be passed to fire rate of spread formulas
fp%vx => grid%uf ! W-E winds used in fire module
fp%vy => grid%vf ! S-N winds used in fire module
fp%zsf => grid%zsf ! terrain height
fp%dzdxf => grid%dzdxf ! terrain grad
fp%dzdyf => grid%dzdyf ! terrain grad
fp%bbb => grid%bbb ! spread formula coeff
fp%betafl => grid%betafl ! spread formula coeff
fp%phiwc => grid%phiwc ! spread formula coeff
fp%r_0 => grid%r_0 ! spread formula coeff
fp%fgip => grid%fgip ! spread formula coeff
fp%ischap => grid%ischap ! spread formula coeff
fp%bbb => grid%bbb ! a rate of spread formula coeff
fp%betafl => grid%betafl ! a rate of spread formula variable
fp%phiwc => grid%phiwc ! a rate of spread formula coeff
fp%r_0 => grid%r_0 ! a rate of spread formula variable
fp%fgip => grid%fgip ! a rate of spread formula coeff
fp%ischap => grid%ischap ! a rate of spread formula switch

! get ignition data
call fire_ignition_convert (config_flags,fire_max_ignitions,fire_ignition_longlat, &
Expand Down Expand Up @@ -350,7 +300,7 @@ subroutine sfire_driver_phys (ifun,need_lfn_update, &
u_frame,v_frame, & ! velocity offset
unit_fxlong,unit_fxlat, & ! fxlong, fxlat units in m
fire_crwn_hgt, & ! lowest height crown fire heat is released (m)
fire_ext_grnd, & ! extinction depth of ground fire heat (m)
fire_ext_grnd, & ! extinction depth of surface fire heat flux (m)
fire_ext_crwn, & ! wind height for vertical interploation to fire spread
fire_wind_height

Expand Down Expand Up @@ -381,14 +331,14 @@ subroutine sfire_driver_phys (ifun,need_lfn_update, &

real, intent(out), dimension(ims:ime, jms:jme):: & ! redundant arrays, for display purposes only (atm grid)
avg_fuel_frac, & ! average fuel fraction
grnhfx, & ! heat flux from ground fire (W/m^2)
grnqfx, & ! moisture flux from ground fire (W/m^2)
grnhfx, & ! heat flux from surface fire (W/m^2)
grnqfx, & ! moisture flux from surface fire (W/m^2)
canhfx, & ! heat flux from crown fire (W/m^2)
canqfx ! moisture flux from crown fire (W/m^2)

real, intent(out), dimension(ifms:ifme, jfms:jfme):: & ! redundant arrays, for display only, fire grid
fgrnhfx, & ! heat flux from ground fire (W/m^2)
fgrnqfx, & ! moisture flux from ground fire (W/m^2)
fgrnhfx, & ! heat flux from surface fire (W/m^2)
fgrnqfx, & ! moisture flux from surface fire (W/m^2)
fcanhfx, & ! heat flux from crown fire (W/m^2)
fcanqfx, & ! moisture flux from crown fire (W/m^2)
ros ! fire rate of spread (m/s)
Expand Down Expand Up @@ -696,7 +646,7 @@ subroutine sfire_driver_phys (ifun,need_lfn_update, &
s = 1./(ir*jr)
do j=jts,jte
do i=its,ite
! scale ground fluxes to get the averages
! scale surface fluxes to get the averages
avg_fuel_frac(i,j)=avg_fuel_frac(i,j)*s
grnhfx(i,j)=fire_atm_feedback*grnhfx(i,j)*s
grnqfx(i,j)=fire_atm_feedback*grnqfx(i,j)*s
Expand Down Expand Up @@ -795,7 +745,7 @@ end subroutine sfire_driver_phys

subroutine fire_ignition_convert (config_flags,fire_max_ignitions,fire_ignition_longlat, &
ignition_line,fire_num_ignitions,unit_fxlong,unit_fxlat)
USE module_configure
USE module_configure, only : grid_config_rec_type
implicit none
! create ignition arrays from scalar flags
!*** arguments
Expand Down Expand Up @@ -1417,8 +1367,6 @@ end subroutine check_fmesh
!*****************************
!
subroutine set_flags(config_flags)
USE module_configure
use module_fr_sfire_util
implicit none
TYPE (grid_config_rec_type) , INTENT(IN) :: config_flags
! copy flags from wrf to module_fr_sfire_util
Expand Down
9 changes: 5 additions & 4 deletions wrfv2_fire/phys/module_fr_sfire_driver_wrf.F
Expand Up @@ -19,8 +19,8 @@ subroutine sfire_driver_em_init (grid , config_flags &

! stub to call sfire_driver_em with irun=0 and omit last 3 args

USE module_domain
USE module_configure
USE module_domain , only: domain , get_ijk_from_subgrid
USE module_configure , only : grid_config_rec_type
implicit none

TYPE(domain) , TARGET :: grid ! data
Expand Down Expand Up @@ -73,8 +73,9 @@ subroutine sfire_driver_em_step (grid , config_flags &

! stub to call sfire_driver_em

USE module_domain
USE module_configure
USE module_domain, only: domain , get_ijk_from_subgrid
USE module_configure , only : grid_config_rec_type
USE module_fr_sfire_util, only : fire_test_steps
implicit none

TYPE(domain) , TARGET :: grid ! data
Expand Down
3 changes: 0 additions & 3 deletions wrfv2_fire/phys/module_fr_sfire_model.F
@@ -1,7 +1,4 @@
!
!*** Jan Mandel October 2007 email: jmandel@ucar.edu or Jan.Mandel@gmail.com
!

#define DEBUG_OUT

module module_fr_sfire_model
Expand Down

0 comments on commit 9a4e383

Please sign in to comment.