Skip to content

Commit

Permalink
Merge branch 'master' into ecosystem_allocation_diags
Browse files Browse the repository at this point in the history
  • Loading branch information
ckoven committed Jun 7, 2018
2 parents 3d9ef64 + 1ccd6bb commit 9b5fa31
Show file tree
Hide file tree
Showing 29 changed files with 6,122 additions and 855 deletions.
45 changes: 35 additions & 10 deletions biogeochem/EDCanopyStructureMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module EDCanopyStructureMod
! =====================================================================================

use FatesConstantsMod , only : r8 => fates_r8
use FatesConstantsMod , only : itrue, ifalse
use FatesGlobals , only : fates_log
use EDPftvarcon , only : EDPftvarcon_inst
use FatesAllometryMod , only : carea_allom
Expand All @@ -18,8 +19,9 @@ module EDCanopyStructureMod
use EDtypesMod , only : AREA
use FatesGlobals , only : endrun => fates_endrun
use FatesInterfaceMod , only : hlm_days_per_year
use FatesInterfaceMod , only : hlm_use_planthydro
use FatesInterfaceMod , only : numpft

use FatesPlantHydraulicsMod, only : UpdateH2OVeg,InitHydrCohort

! CIME Globals
use shr_log_mod , only : errMsg => shr_log_errMsg
Expand Down Expand Up @@ -172,7 +174,7 @@ subroutine canopy_structure( currentSite , bc_in )
! Remove cohorts that are incredibly sparse
call terminate_cohorts(currentSite, currentPatch, 1)

call fuse_cohorts(currentPatch, bc_in)
call fuse_cohorts(currentSite, currentPatch, bc_in)

! Remove cohorts for various other reasons
call terminate_cohorts(currentSite, currentPatch, 2)
Expand All @@ -196,7 +198,7 @@ subroutine canopy_structure( currentSite , bc_in )
! Remove cohorts that are incredibly sparse
call terminate_cohorts(currentSite, currentPatch, 1)

call fuse_cohorts(currentPatch, bc_in)
call fuse_cohorts(currentSite, currentPatch, bc_in)

! Remove cohorts for various other reasons
call terminate_cohorts(currentSite, currentPatch, 2)
Expand Down Expand Up @@ -390,6 +392,9 @@ subroutine DemoteFromLayer(currentSite,currentPatch,i_lyr)
! otherwise currentPatch%spread(i_lyr+1) will be higher and the area will change...!!!

allocate(copyc)
if( hlm_use_planthydro.eq.itrue ) then
call InitHydrCohort(currentSite,copyc)
endif
call copy_cohort(currentCohort, copyc) !

newarea = currentCohort%c_area - cc_loss
Expand Down Expand Up @@ -460,7 +465,7 @@ subroutine DemoteFromLayer(currentSite,currentPatch,i_lyr)
call carea_allom(currentCohort%dbh,currentCohort%n, &
currentSite%spread,currentCohort%pft,currentCohort%c_area)
endif

call carea_allom(copyc%dbh,copyc%n,currentSite%spread,copyc%pft,copyc%c_area)


Expand Down Expand Up @@ -535,7 +540,8 @@ subroutine DemoteFromLayer(currentSite,currentPatch,i_lyr)
currentCohort%c_area = 0._r8

else
call carea_allom(currentCohort%dbh,currentCohort%n,currentSite%spread,currentCohort%pft,currentCohort%c_area)
call carea_allom(currentCohort%dbh,currentCohort%n,currentSite%spread, &
currentCohort%pft,currentCohort%c_area)
endif

endif ! matches: if (cc_loss < currentCohort%c_area)then
Expand Down Expand Up @@ -715,6 +721,9 @@ subroutine PromoteIntoLayer(currentSite,currentPatch,i_lyr)
!-----------Split and copy boundary cohort-----------------!
if(cc_gain < currentCohort%c_area)then
allocate(copyc)
if( hlm_use_planthydro.eq.itrue ) then
call InitHydrCohort(CurrentSite,copyc)
endif

call copy_cohort(currentCohort, copyc) !makes an identical copy...
! n.b this needs to happen BEFORE the cohort goes into the new layer, otherwise currentPatch
Expand Down Expand Up @@ -882,10 +891,11 @@ subroutine canopy_summarization( nsites, sites, bc_in )

use FatesInterfaceMod , only : bc_in_type
use EDPatchDynamicsMod , only : set_patchno
use EDPatchDynamicsMod , only : set_root_fraction
use FatesAllometryMod , only : set_root_fraction
use FatesAllometryMod , only : i_hydro_rootprof_context
use FatesSizeAgeTypeIndicesMod, only : sizetype_class_index
use EDtypesMod , only : area
use EDPftvarcon , only : EDPftvarcon_inst
use EDPftvarcon , only : EDPftvarcon_inst

! !ARGUMENTS
integer , intent(in) :: nsites
Expand Down Expand Up @@ -920,8 +930,18 @@ subroutine canopy_summarization( nsites, sites, bc_in )

do while(associated(currentPatch))

call set_root_fraction(currentPatch,bc_in(s)%zi_sisl)

! Calculate rooting depth fractions for the patch x pft
! Note that we are calling for the root fractions in the hydrologic context.
! See explanation in FatesAllometryMod. In other locations, this
! function is called to return the profile of biomass as used for litter

do ft = 1, numpft
call set_root_fraction(currentPatch%rootfr_ft(ft,1:bc_in(s)%nlevsoil), ft, &
bc_in(s)%zi_sisl,lowerb=lbound(bc_in(s)%zi_sisl,1), &
icontext=i_hydro_rootprof_context)
end do


!zero cohort-summed variables.
currentPatch%total_canopy_area = 0.0_r8
currentPatch%total_tree_area = 0.0_r8
Expand All @@ -934,6 +954,7 @@ subroutine canopy_summarization( nsites, sites, bc_in )
ft = currentCohort%pft



! Update the cohort's index within the size bin classes
! Update the cohort's index within the SCPF classification system
call sizetype_class_index(currentCohort%dbh,currentCohort%pft, &
Expand Down Expand Up @@ -1588,10 +1609,14 @@ subroutine update_hlm_dynamics(nsites,sites,fcolumn,bc_out)
if(abs(total_patch_area-1.0_r8)>1e-9)then
write(fates_log(),*) 'total area is wrong in update_hlm_dynamics',total_patch_area
endif


end do

! If hydraulics is turned on, update the amount of water bound in vegetation
if (hlm_use_planthydro.eq.itrue) then
call UpdateH2OVeg(nsites,sites,bc_out)
end if


end subroutine update_hlm_dynamics

Expand Down
37 changes: 25 additions & 12 deletions biogeochem/EDCohortDynamicsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ module EDCohortDynamicsMod
use FatesPlantHydraulicsMod, only : initTreeHydStates
use FatesPlantHydraulicsMod, only : InitHydrCohort
use FatesPlantHydraulicsMod, only : DeallocateHydrCohort
use FatesPlantHydraulicsMod, only : AccumulateMortalityWaterStorage
use FatesSizeAgeTypeIndicesMod, only : sizetype_class_index
use FatesAllometryMod , only : bsap_allom
use FatesAllometryMod , only : bleaf
Expand Down Expand Up @@ -64,19 +65,23 @@ module EDCohortDynamicsMod
contains

!-------------------------------------------------------------------------------------!
subroutine create_cohort(patchptr, pft, nn, hite, dbh, bleaf, bfineroot, bsap, &
bdead, bstore, laimemory, status, ctrim, clayer, spread, bc_in)

subroutine create_cohort(currentSite, patchptr, pft, nn, hite, dbh, bleaf, bfineroot, bsap, &
bdead, bstore, laimemory, status, recruitstatus,ctrim, clayer, spread, bc_in)

!
! !DESCRIPTION:
! create new cohort
!
! !USES:
!
! !ARGUMENTS
type(ed_site_type), intent(inout), target :: currentSite
type(ed_patch_type), intent(inout), pointer :: patchptr
integer, intent(in) :: pft ! Cohort Plant Functional Type
integer, intent(in) :: clayer ! canopy status of cohort (1 = canopy, 2 = understorey, etc.)
integer, intent(in) :: status ! growth status of plant (2 = leaves on , 1 = leaves off)
integer, intent(in) :: recruitstatus ! recruit status of plant (1 = recruitment , 0 = other)
real(r8), intent(in) :: nn ! number of individuals in cohort per 'area' (10000m2 default)
real(r8), intent(in) :: hite ! height: meters
real(r8), intent(in) :: dbh ! dbh: cm
Expand All @@ -89,6 +94,7 @@ subroutine create_cohort(patchptr, pft, nn, hite, dbh, bleaf, bfineroot, bsap, &
real(r8), intent(in) :: ctrim ! What is the fraction of the maximum leaf biomass that we are targeting? :-
real(r8), intent(in) :: spread ! The community assembly effects how spread crowns are in horizontal space
type(bc_in_type), intent(in) :: bc_in ! External boundary conditions

!
! !LOCAL VARIABLES:
type(ed_cohort_type), pointer :: new_cohort ! Pointer to New Cohort structure.
Expand Down Expand Up @@ -178,9 +184,12 @@ subroutine create_cohort(patchptr, pft, nn, hite, dbh, bleaf, bfineroot, bsap, &
new_cohort%isnew = .true.

if( hlm_use_planthydro.eq.itrue ) then
call InitHydrCohort(new_cohort)
call updateSizeDepTreeHydProps(new_cohort, bc_in)
call initTreeHydStates(new_cohort, bc_in)
call InitHydrCohort(CurrentSite,new_cohort)
call updateSizeDepTreeHydProps(CurrentSite,new_cohort, bc_in)
call initTreeHydStates(CurrentSite,new_cohort, bc_in)
if(recruitstatus==1)then
new_cohort%co_hydr%is_newly_recuited = .true.
endif
endif

call insert_cohort(new_cohort, patchptr%tallest, patchptr%shortest, tnull, snull, &
Expand Down Expand Up @@ -241,7 +250,7 @@ subroutine nan_cohort(cc_p)
currentCohort%br = nan ! fine root biomass: kGC per indiv
currentCohort%lai = nan ! leaf area index of cohort m2/m2
currentCohort%sai = nan ! stem area index of cohort m2/m2
currentCohort%gscan = nan ! Stomatal resistance of cohort.
currentCohort%g_sb_laweight = nan ! Total leaf conductance of cohort (stomata+blayer) weighted by leaf-area [m/s]*[m2]
currentCohort%canopy_trim = nan ! What is the fraction of the maximum leaf biomass that we are targeting? :-
currentCohort%leaf_cost = nan ! How much does it cost to maintain leaves: kgC/m2/year-1
currentCohort%excl_weight = nan ! How much of this cohort is demoted each year, as a proportion of all cohorts:-
Expand Down Expand Up @@ -362,7 +371,7 @@ subroutine zero_cohort(cc_p)
currentcohort%npp_acc_hold = 0._r8
currentcohort%gpp_acc_hold = 0._r8
currentcohort%dmort = 0._r8
currentcohort%gscan = 0._r8
currentcohort%g_sb_laweight = 0._r8
currentcohort%treesai = 0._r8
currentCohort%lmort_direct = 0._r8
currentCohort%lmort_infra = 0._r8
Expand Down Expand Up @@ -535,6 +544,7 @@ subroutine terminate_cohorts( currentSite, currentPatch, level )
if(associated(shorterCohort)) shorterCohort%taller => null()
else
tallerCohort%shorter => shorterCohort

endif

if (.not. associated(shorterCohort)) then
Expand All @@ -557,7 +567,7 @@ end subroutine terminate_cohorts

!-------------------------------------------------------------------------------------!

subroutine fuse_cohorts(currentPatch, bc_in)
subroutine fuse_cohorts(currentSite, currentPatch, bc_in)

!
! !DESCRIPTION:
Expand All @@ -567,7 +577,8 @@ subroutine fuse_cohorts(currentPatch, bc_in)
use EDParamsMod , only : ED_val_cohort_fusion_tol
use shr_infnan_mod, only : nan => shr_infnan_nan, assignment(=)
!
! !ARGUMENTS
! !ARGUMENTS
type (ed_site_type), intent(inout), target :: currentSite
type (ed_patch_type), intent(inout), target :: currentPatch
type (bc_in_type), intent(in) :: bc_in
!
Expand Down Expand Up @@ -711,7 +722,7 @@ subroutine fuse_cohorts(currentPatch, bc_in)
call sizetype_class_index(currentCohort%dbh,currentCohort%pft, &
currentCohort%size_class,currentCohort%size_by_pft_class)

if(hlm_use_planthydro.eq.itrue) call FuseCohortHydraulics(currentCohort,nextc,bc_in,newn)
if(hlm_use_planthydro.eq.itrue) call FuseCohortHydraulics(currentSite,currentCohort,nextc,bc_in,newn)

! recent canopy history
currentCohort%canopy_layer_yesterday = (currentCohort%n*currentCohort%canopy_layer_yesterday + &
Expand Down Expand Up @@ -1112,7 +1123,7 @@ subroutine copy_cohort( currentCohort,copyc )
n%br = o%br
n%lai = o%lai
n%sai = o%sai
n%gscan = o%gscan
n%g_sb_laweight = o%g_sb_laweight
n%leaf_cost = o%leaf_cost
n%canopy_layer = o%canopy_layer
n%canopy_layer_yesterday = o%canopy_layer_yesterday
Expand Down Expand Up @@ -1209,7 +1220,9 @@ subroutine copy_cohort( currentCohort,copyc )

! Plant Hydraulics

if( hlm_use_planthydro.eq.itrue ) call CopyCohortHydraulics(n,o)
if( hlm_use_planthydro.eq.itrue ) then
call CopyCohortHydraulics(n,o)
endif

! indices for binning
n%size_class = o%size_class
Expand Down
12 changes: 10 additions & 2 deletions biogeochem/EDLoggingMortalityMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -38,12 +38,14 @@ module EDLoggingMortalityMod
use FatesInterfaceMod , only : hlm_model_day
use FatesInterfaceMod , only : hlm_day_of_year
use FatesInterfaceMod , only : hlm_days_per_year
use FatesInterfaceMod , only : hlm_use_logging
use FatesInterfaceMod , only : hlm_use_logging
use FatesInterfaceMod , only : hlm_use_planthydro
use FatesConstantsMod , only : itrue,ifalse
use FatesGlobals , only : endrun => fates_endrun
use FatesGlobals , only : fates_log
use shr_log_mod , only : errMsg => shr_log_errMsg

use FatesPlantHydraulicsMod, only : AccumulateMortalityWaterStorage

implicit none
private

Expand Down Expand Up @@ -296,6 +298,12 @@ subroutine logging_litter_fluxes(currentSite, currentPatch, newPatch, patch_site
litter_area = currentPatch%area
np_mult = patch_site_areadis/newPatch%area


if( hlm_use_planthydro == itrue ) then
call AccumulateMortalityWaterStorage(currentSite,currentCohort,(direct_dead+indirect_dead))
end if


! ----------------------------------------------------------------------------------------
! Handle woody litter flux for non-bole components of biomass
! This litter is distributed between the current and new patches, &
Expand Down
11 changes: 5 additions & 6 deletions biogeochem/EDMortalityFunctionsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -60,10 +60,9 @@ subroutine mortality_rates( cohort_in,bc_in,cmort,hmort,bmort,frmort )
real(r8) :: frac ! relativised stored carbohydrate
real(r8) :: b_leaf ! target leaf biomass kgC
real(r8) :: hf_sm_threshold ! hydraulic failure soil moisture threshold
real(r8) :: temp_dep ! Temp. function (freezing mortality)
real(r8) :: temp_dep_fraction ! Temp. function (freezing mortality)
real(r8) :: temp_in_C ! Daily averaged temperature in Celcius
real(r8),parameter :: frost_mort_buffer = 5.0_r8 ! 5deg buffer for freezing mortality

real(r8), parameter :: frost_mort_buffer = 5.0_r8 ! 5deg buffer for freezing mortality
logical, parameter :: test_zero_mortality = .false. ! Developer test which
! may help to debug carbon imbalances
! and the like
Expand Down Expand Up @@ -107,9 +106,9 @@ subroutine mortality_rates( cohort_in,bc_in,cmort,hmort,bmort,frmort )
! doi: 10.1111/j.1365-2486.2006.01254.x

temp_in_C = bc_in%t_veg24_si - tfrz
temp_dep = max(0.0,min(1.0,1.0 - (temp_in_C - &
EDPftvarcon_inst%freezetol(cohort_in%pft))/frost_mort_buffer) )
frmort = EDPftvarcon_inst%mort_scalar_coldstress(cohort_in%pft) * temp_dep
temp_dep_fraction = max(0.0_r8, min(1.0_r8, 1.0_r8 - (temp_in_C - &
EDPftvarcon_inst%freezetol(cohort_in%pft))/frost_mort_buffer) )
frmort = EDPftvarcon_inst%mort_scalar_coldstress(cohort_in%pft) * temp_dep_fraction


!mortality_rates = bmort + hmort + cmort
Expand Down
Loading

0 comments on commit 9b5fa31

Please sign in to comment.