Skip to content

Commit

Permalink
Merge pull request #381 from rgknox/rgknox-soildepth-clm5
Browse files Browse the repository at this point in the history
variable soil depth compatibility with CLM5
  • Loading branch information
rgknox authored Jun 1, 2018
2 parents 1495bbb + 02792d0 commit 14aeb4f
Show file tree
Hide file tree
Showing 15 changed files with 856 additions and 493 deletions.
24 changes: 18 additions & 6 deletions biogeochem/EDCanopyStructureMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -393,7 +393,7 @@ subroutine DemoteFromLayer(currentSite,currentPatch,i_lyr)

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

Expand Down Expand Up @@ -722,7 +722,7 @@ subroutine PromoteIntoLayer(currentSite,currentPatch,i_lyr)
if(cc_gain < currentCohort%c_area)then
allocate(copyc)
if( hlm_use_planthydro.eq.itrue ) then
call InitHydrCohort(copyc)
call InitHydrCohort(CurrentSite,copyc)
endif

call copy_cohort(currentCohort, copyc) !makes an identical copy...
Expand Down Expand Up @@ -891,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 @@ -929,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 @@ -943,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
6 changes: 3 additions & 3 deletions biogeochem/EDCohortDynamicsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -184,9 +184,9 @@ subroutine create_cohort(currentSite, patchptr, pft, nn, hite, dbh, bleaf, bfine
new_cohort%isnew = .true.

if( hlm_use_planthydro.eq.itrue ) then
call InitHydrCohort(new_cohort)
call updateSizeDepTreeHydProps(new_cohort, bc_in)
call initTreeHydStates(currentSite,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
Expand Down
60 changes: 12 additions & 48 deletions biogeochem/EDPatchDynamicsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,6 @@ module EDPatchDynamicsMod
use EDTypesMod , only : dtype_ilog
use EDTypesMod , only : dtype_ifire
use FatesInterfaceMod , only : hlm_use_planthydro
use FatesInterfaceMod , only : hlm_numlevgrnd
use FatesInterfaceMod , only : hlm_numlevsoil
use FatesInterfaceMod , only : hlm_numSWb
use FatesInterfaceMod , only : bc_in_type
use FatesInterfaceMod , only : hlm_days_per_year
Expand Down Expand Up @@ -57,7 +55,6 @@ module EDPatchDynamicsMod
public :: disturbance_rates
public :: check_patch_area
public :: set_patchno
public :: set_root_fraction
private:: fuse_2_patches

character(len=*), parameter, private :: sourcefile = &
Expand Down Expand Up @@ -346,7 +343,7 @@ subroutine spawn_patches( currentSite, bc_in)
allocate(new_patch)
call create_patch(currentSite, new_patch, age, site_areadis, &
cwd_ag_local, cwd_bg_local, leaf_litter_local, &
root_litter_local)
root_litter_local, bc_in%nlevsoil)

new_patch%tallest => null()
new_patch%shortest => null()
Expand Down Expand Up @@ -381,7 +378,7 @@ subroutine spawn_patches( currentSite, bc_in)
do while(associated(currentCohort))

allocate(nc)
if(hlm_use_planthydro.eq.itrue) call InitHydrCohort(nc)
if(hlm_use_planthydro.eq.itrue) call InitHydrCohort(CurrentSite,nc)
call zero_cohort(nc)

! nc is the new cohort that goes in the disturbed patch (new_patch)... currentCohort
Expand Down Expand Up @@ -1135,7 +1132,7 @@ end subroutine mortality_litter_fluxes

! ============================================================================
subroutine create_patch(currentSite, new_patch, age, areap,cwd_ag_local,cwd_bg_local, &
leaf_litter_local,root_litter_local)
leaf_litter_local,root_litter_local,nlevsoil)
!
! !DESCRIPTION:
! Set default values for creating a new patch
Expand All @@ -1145,12 +1142,13 @@ subroutine create_patch(currentSite, new_patch, age, areap,cwd_ag_local,cwd_bg_l
! !ARGUMENTS:
type(ed_site_type) , intent(inout), target :: currentSite
type(ed_patch_type), intent(inout), target :: new_patch
real(r8), intent(in) :: age ! notional age of this patch in years
real(r8), intent(in) :: areap ! initial area of this patch in m2.
real(r8), intent(in) :: cwd_ag_local(:) ! initial value of above ground coarse woody debris. KgC/m2
real(r8), intent(in) :: cwd_bg_local(:) ! initial value of below ground coarse woody debris. KgC/m2
real(r8), intent(in) :: root_litter_local(:)! initial value of root litter. KgC/m2
real(r8), intent(in) :: leaf_litter_local(:)! initial value of leaf litter. KgC/m2
real(r8), intent(in) :: age ! notional age of this patch in years
real(r8), intent(in) :: areap ! initial area of this patch in m2.
real(r8), intent(in) :: cwd_ag_local(:) ! initial value of above ground coarse woody debris. KgC/m2
real(r8), intent(in) :: cwd_bg_local(:) ! initial value of below ground coarse woody debris. KgC/m2
real(r8), intent(in) :: root_litter_local(:) ! initial value of root litter. KgC/m2
real(r8), intent(in) :: leaf_litter_local(:) ! initial value of leaf litter. KgC/m2
integer, intent(in) :: nlevsoil ! number of soil layers
!
! !LOCAL VARIABLES:
!---------------------------------------------------------------------
Expand All @@ -1163,8 +1161,8 @@ subroutine create_patch(currentSite, new_patch, age, areap,cwd_ag_local,cwd_bg_l
allocate(new_patch%fabi(hlm_numSWb))
allocate(new_patch%sabs_dir(hlm_numSWb))
allocate(new_patch%sabs_dif(hlm_numSWb))
allocate(new_patch%rootfr_ft(numpft,hlm_numlevgrnd))
allocate(new_patch%rootr_ft(numpft,hlm_numlevgrnd))
allocate(new_patch%rootfr_ft(numpft,nlevsoil))
allocate(new_patch%rootr_ft(numpft,nlevsoil))

call zero_patch(new_patch) !The nan value in here is not working??

Expand Down Expand Up @@ -1909,38 +1907,4 @@ function countPatches( nsites, sites ) result ( totNumPatches )

end function countPatches

! ====================================================================================

subroutine set_root_fraction( cpatch , zi )
!
! !DESCRIPTION:
! Calculates the fractions of the root biomass in each layer for each pft.
!
! !USES:

!
! !ARGUMENTS
type(ed_patch_type),intent(inout), target :: cpatch
real(r8),intent(in) :: zi(0:hlm_numlevsoil)
!
! !LOCAL VARIABLES:
integer :: lev,p,c,ft
!----------------------------------------------------------------------

do ft = 1,numpft
do lev = 1, hlm_numlevgrnd
cpatch%rootfr_ft(ft,lev) = 0._r8
enddo

do lev = 1, hlm_numlevsoil-1
cpatch%rootfr_ft(ft,lev) = .5_r8*( &
exp(-EDPftvarcon_inst%roota_par(ft) * zi(lev-1)) &
+ exp(-EDPftvarcon_inst%rootb_par(ft) * zi(lev-1)) &
- exp(-EDPftvarcon_inst%roota_par(ft) * zi(lev)) &
- exp(-EDPftvarcon_inst%rootb_par(ft) * zi(lev)))
end do
end do

end subroutine set_root_fraction

end module EDPatchDynamicsMod
Loading

0 comments on commit 14aeb4f

Please sign in to comment.