Skip to content

Commit

Permalink
Merge pull request #468 from rgknox/rgknox-fix-10day-phen
Browse files Browse the repository at this point in the history
phenology status timers
  • Loading branch information
glemieux authored May 6, 2019
2 parents 30a9310 + 4b7293d commit d2f0907
Show file tree
Hide file tree
Showing 10 changed files with 592 additions and 342 deletions.
452 changes: 274 additions & 178 deletions biogeochem/EDPhysiologyMod.F90

Large diffs are not rendered by default.

130 changes: 68 additions & 62 deletions main/EDInitMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module EDInitMod
use FatesConstantsMod , only : r8 => fates_r8
use FatesConstantsMod , only : ifalse
use FatesConstantsMod , only : itrue
use FatesConstantsMod , only : fates_unset_int
use FatesConstantsMod , only : primaryforest
use FatesGlobals , only : endrun => fates_endrun
use EDTypesMod , only : nclmax
Expand All @@ -17,14 +18,21 @@ module EDInitMod
use EDPatchDynamicsMod , only : create_patch
use EDTypesMod , only : ed_site_type, ed_patch_type, ed_cohort_type
use EDTypesMod , only : ncwd
use EDTypesMod , only : nuMWaterMem
use EDTypesMod , only : numWaterMem
use EDTypesMod , only : num_vegtemp_mem
use EDTypesMod , only : maxpft
use EDTypesMod , only : AREA
use EDTypesMod , only : init_spread_near_bare_ground
use EDTypesMod , only : init_spread_inventory
use EDTypesMod , only : first_leaf_aclass
use EDTypesMod , only : leaves_on
use EDTypesMod , only : leaves_off
use EDTypesMod , only : phen_cstat_nevercold
use EDTypesMod , only : phen_cstat_iscold
use EDTypesMod , only : phen_dstat_timeoff
use EDTypesMod , only : phen_dstat_moistoff
use EDTypesMod , only : phen_cstat_notcold
use EDTypesMod , only : phen_dstat_moiston
use FatesInterfaceMod , only : bc_in_type
use FatesInterfaceMod , only : hlm_use_planthydro
use FatesInterfaceMod , only : hlm_use_inventory_init
Expand Down Expand Up @@ -110,17 +118,18 @@ subroutine zero_site( site_in )
site_in%total_burn_flux_to_atm = 0._r8

! PHENOLOGY
site_in%is_cold = .false. ! Is cold deciduous leaf-off triggered?
site_in%is_drought = .false. ! Is drought deciduous leaf-off triggered?
site_in%ED_GDD_site = nan ! growing degree days
site_in%ncd = nan ! no chilling days
site_in%last_n_days(:) = 999 ! record of last 10 days temperature for senescence model.
site_in%leafondate = 999 ! doy of leaf on
site_in%leafoffdate = 999 ! doy of leaf off
site_in%dleafondate = 999 ! doy of leaf on drought
site_in%dleafoffdate = 999 ! doy of leaf on drought
site_in%water_memory(:) = nan

site_in%cstatus = fates_unset_int ! are leaves in this pixel on or off?
site_in%dstatus = fates_unset_int
site_in%grow_deg_days = nan ! growing degree days
site_in%nchilldays = fates_unset_int
site_in%ncolddays = fates_unset_int
site_in%cleafondate = fates_unset_int ! doy of leaf on
site_in%cleafoffdate = fates_unset_int ! doy of leaf off
site_in%dleafondate = fates_unset_int ! doy of leaf on drought
site_in%dleafoffdate = fates_unset_int ! doy of leaf on drought
site_in%water_memory(:) = nan
site_in%vegtemp_memory(:) = nan ! record of last 10 days temperature for senescence model.

! SEED
site_in%seed_bank(:) = 0._r8
Expand Down Expand Up @@ -185,66 +194,61 @@ subroutine set_site_properties( nsites, sites)
!
! !LOCAL VARIABLES:
integer :: s
real(r8) :: leafon
real(r8) :: leafoff
logical :: stat
real(r8) :: NCD
integer :: cstat ! cold status phenology flag
real(r8) :: GDD
logical :: dstat
integer :: dstat ! drought status phenology flag
real(r8) :: acc_NI
real(r8) :: watermem
integer :: dleafoff
integer :: dleafon
real(r8) :: watermem
integer :: cleafon ! DOY for cold-decid leaf-on, initial guess
integer :: cleafoff ! DOY for cold-decid leaf-off, initial guess
integer :: dleafoff ! DOY for drought-decid leaf-off, initial guess
integer :: dleafon ! DOY for drought-decid leaf-on, initial guess
!----------------------------------------------------------------------

if ( hlm_is_restart == ifalse ) then
!initial guess numbers for site condition.
NCD = 0.0_r8
GDD = 30.0_r8
leafon = 100.0_r8
leafoff = 300.0_r8
stat = .false.
acc_NI = 0.0_r8
dstat = .false.
dleafoff = 300
dleafon = 100
watermem = 0.5_r8

else ! assignements for restarts
! If this is not a restart, we need to start with some reasonable
! starting points. If this is a restart, we leave the values
! as unset ints and reals, and let the restart values be read in
! after this routine

if ( hlm_is_restart == ifalse ) then

NCD = 1.0_r8 ! NCD should be 1 on restart
GDD = 0.0_r8
leafon = 0.0_r8
leafoff = 0.0_r8
stat = .false.
GDD = 30.0_r8
cleafon = 100
cleafoff = 300
cstat = phen_cstat_notcold ! Leaves are on
acc_NI = 0.0_r8
dstat = .false.
dstat = phen_dstat_moiston ! Leaves are on
dleafoff = 300
dleafon = 100
watermem = 0.5_r8

endif

do s = 1,nsites
sites(s)%ncd = NCD
sites(s)%leafondate = leafon
sites(s)%leafoffdate = leafoff
sites(s)%dleafoffdate = dleafoff
sites(s)%dleafondate = dleafon
sites(s)%ED_GDD_site = GDD

if ( hlm_is_restart == ifalse ) then
do s = 1,nsites
sites(s)%nchilldays = 0
sites(s)%ncolddays = 0 ! recalculated in phenology
! immediately, so yes this
! is memory-less, but needed
! for first value in history file

sites(s)%cleafondate = cleafon
sites(s)%cleafoffdate = cleafoff
sites(s)%dleafoffdate = dleafoff
sites(s)%dleafondate = dleafon
sites(s)%grow_deg_days = GDD

sites(s)%water_memory(1:numWaterMem) = watermem
end if

sites(s)%is_cold = stat
sites(s)%is_drought = dstat

sites(s)%acc_NI = acc_NI
sites(s)%frac_burnt = 0.0_r8
sites(s)%old_stock = 0.0_r8

end do
sites(s)%vegtemp_memory(1:num_vegtemp_mem) = 0._r8

sites(s)%cstatus = cstat
sites(s)%dstatus = dstat

sites(s)%acc_NI = acc_NI
sites(s)%frac_burnt = 0.0_r8
sites(s)%old_stock = 0.0_r8

end do

end if

return
end subroutine set_site_properties
Expand Down Expand Up @@ -439,13 +443,15 @@ subroutine init_cohorts( site_in, patch_in, bc_in)
temp_cohort%laimemory = 0._r8
cstatus = leaves_on

if( EDPftvarcon_inst%season_decid(pft) == itrue .and. site_in%is_cold ) then
if( EDPftvarcon_inst%season_decid(pft) == itrue .and. &
any(site_in%cstatus == [phen_cstat_nevercold,phen_cstat_iscold])) then
temp_cohort%laimemory = b_leaf
b_leaf = 0._r8
cstatus = leaves_off
endif

if ( EDPftvarcon_inst%stress_decid(pft) == itrue .and. site_in%is_drought ) then

if ( EDPftvarcon_inst%stress_decid(pft) == itrue .and. &
any(site_in%dstatus == [phen_dstat_timeoff,phen_dstat_moistoff])) then
temp_cohort%laimemory = b_leaf
b_leaf = 0._r8
cstatus = leaves_off
Expand Down
15 changes: 11 additions & 4 deletions main/EDMainMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,8 @@ module EDMainMod
use EDtypesMod , only : ed_patch_type
use EDtypesMod , only : ed_cohort_type
use EDTypesMod , only : AREA
use EDTypesMod , only : phen_dstat_moiston
use EDTypesMod , only : phen_dstat_timeon
use FatesConstantsMod , only : itrue,ifalse
use FatesConstantsMod , only : primaryforest, secondaryforest
use FatesPlantHydraulicsMod , only : do_growthrecruiteffects
Expand Down Expand Up @@ -270,6 +272,7 @@ subroutine ed_integrate_state_variables(currentSite, bc_in )
real(r8) :: cohort_biomass_store ! remembers the biomass in the cohort for balance checking
real(r8) :: dbh_old ! dbh of plant before daily PRT [cm]
real(r8) :: hite_old ! height of plant before daily PRT [m]
logical :: is_drought ! logical for if the plant (site) is in a drought state
real(r8) :: leaf_c
real(r8) :: delta_dbh ! correction for dbh
real(r8) :: delta_hite ! correction for hite
Expand Down Expand Up @@ -361,9 +364,13 @@ subroutine ed_integrate_state_variables(currentSite, bc_in )


! Conduct Maintenance Turnover (parteh)

call currentCohort%prt%CheckMassConservation(ft,3)
call PRTMaintTurnover(currentCohort%prt,ft,currentSite%is_drought)
if(any(currentSite%dstatus == [phen_dstat_moiston,phen_dstat_timeon])) then
is_drought = .false.
else
is_drought = .true.
end if
call PRTMaintTurnover(currentCohort%prt,ft,is_drought)
call currentCohort%prt%CheckMassConservation(ft,4)

leaf_c = currentCohort%prt%GetState(leaf_organ, all_carbon_elements)
Expand Down Expand Up @@ -750,8 +757,8 @@ subroutine bypass_dynamics(currentSite)
currentCohort%frmort = 0.0_r8

currentCohort%dndt = 0.0_r8
currentCohort%dhdt = 0.0_r8
currentCohort%ddbhdt = 0.0_r8
currentCohort%dhdt = 0.0_r8
currentCohort%ddbhdt = 0.0_r8

currentCohort => currentCohort%taller
enddo
Expand Down
46 changes: 36 additions & 10 deletions main/EDTypesMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,7 @@ module EDTypesMod

integer, parameter :: leaves_on = 2 ! Flag specifying that a deciduous plant has leaves
! and should be allocating to them as well

integer, parameter :: leaves_off = 1 ! Flag specifying that a deciduous plant has dropped
! its leaves and should not be trying to allocate
! towards any growth.
Expand Down Expand Up @@ -107,14 +108,28 @@ module EDTypesMod
integer, parameter :: numWaterMem = 10 ! watermemory saved as site level var

! BIOLOGY/BIOGEOCHEMISTRY
integer , parameter :: SENES = 10 ! Window of time over which we track temp for cold sensecence (days)
integer , parameter :: num_vegtemp_mem = 10 ! Window of time over which we track temp for cold sensecence (days)
real(r8), parameter :: dinc_ed = 1.0_r8 ! size of VAI bins (LAI+SAI) [CHANGE THIS NAME WITH NEXT INTERFACE
! UPDATE]
integer , parameter :: N_DIST_TYPES = 3 ! Disturbance Modes 1) tree-fall, 2) fire, 3) logging
integer , parameter :: dtype_ifall = 1 ! index for naturally occuring tree-fall generated event
integer , parameter :: dtype_ifire = 2 ! index for fire generated disturbance event
integer , parameter :: dtype_ilog = 3 ! index for logging generated disturbance event


! Phenology status flag definitions (cold type is cstat, dry type is dstat)

integer, parameter :: phen_cstat_nevercold = 0 ! This (location/plant) has not experienced a cold period over a large number
! of days, leaves are dropped and flagged as non-cold region
integer, parameter :: phen_cstat_iscold = 1 ! This (location/plant) is in a cold-state where leaves should have fallen
integer, parameter :: phen_cstat_notcold = 2 ! This site is in a warm-state where leaves are allowed to flush

integer, parameter :: phen_dstat_timeoff = 0 ! Leaves off due to time exceedance (drought phenology)
integer, parameter :: phen_dstat_moistoff = 1 ! Leaves off due to moisture avail (drought phenology)
integer, parameter :: phen_dstat_moiston = 2 ! Leaves on due to moisture avail (drought phenology)
integer, parameter :: phen_dstat_timeon = 3 ! Leaves on due to time exceedance (drought phenology)


! SPITFIRE
integer, parameter :: NCWD = 4 ! number of coarse woody debris pools (twig,s branch,l branch, trunk)
integer , parameter :: NFSC = NCWD+2 ! number fuel size classes (4 cwd size classes, leaf litter, and grass)
Expand Down Expand Up @@ -611,15 +626,26 @@ module EDTypesMod


! PHENOLOGY
real(r8) :: ED_GDD_site ! ED Phenology growing degree days.
logical :: is_cold ! is this site/column in a cold-status where its cohorts drop leaves?
logical :: is_drought ! is this site/column in a drought-status where its cohorts drop leaves?
real(r8) :: ncd ! no chilling days:-
real(r8) :: last_n_days(senes) ! record of last 10 days temperature for senescence model. deg C
integer :: leafondate ! doy of leaf on:-
integer :: leafoffdate ! doy of leaf off:-
integer :: dleafondate ! doy of leaf on drought:-
integer :: dleafoffdate ! doy of leaf on drought:-
real(r8) :: grow_deg_days ! Phenology growing degree days

integer :: cstatus ! are leaves in this pixel on or off for cold decid
! 0 = this site has not experienced a cold period over at least
! 400 days, leaves are dropped and flagged as non-cold region
! 1 = this site is in a cold-state where leaves should have fallen
! 2 = this site is in a warm-state where leaves are allowed to flush
integer :: dstatus ! are leaves in this pixel on or off for drought decid
! 0 = leaves off due to time exceedance
! 1 = leaves off due to moisture avail
! 2 = leaves on due to moisture avail
! 3 = leaves on due to time exceedance
integer :: nchilldays ! num chilling days: (for botta gdd trheshold calculation)
integer :: ncolddays ! num cold days: (must exceed threshold to drop leaves)
real(r8) :: vegtemp_memory(num_vegtemp_mem) ! record of last 10 days temperature for senescence model. deg C
integer :: cleafondate ! model date (day integer) of leaf on (cold):-
integer :: cleafoffdate ! model date (day integer) of leaf off (cold):-
integer :: dleafondate ! model date (day integer) of leaf on drought:-
integer :: dleafoffdate ! model date (day integer) of leaf off drought:-

real(r8) :: water_memory(numWaterMem) ! last 10 days of soil moisture memory...

!SEED BANK
Expand Down
8 changes: 5 additions & 3 deletions main/FatesConstantsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -15,10 +15,12 @@ module FatesConstantsMod
integer, parameter :: fates_short_string_length = 32
integer, parameter :: fates_long_string_length = 199

! Unset and various other 'special' values
! Used to initialize and test unset integers
integer, parameter :: fates_unset_int = -9999
real(fates_r8), parameter :: fates_unset_r8 = -9999._fates_r8


! Used to initialize and test unset r8s
real(fates_r8), parameter :: fates_unset_r8 = -1.e36_fates_r8

! Integer equivalent of true (in case some compilers dont auto convert)
integer, parameter :: itrue = 1

Expand Down
Loading

0 comments on commit d2f0907

Please sign in to comment.