Skip to content

Commit

Permalink
Initialized plant cohorts with more than one PFT
Browse files Browse the repository at this point in the history
  • Loading branch information
Laura Marques committed Apr 26, 2024
1 parent e282cd8 commit 73be8fa
Show file tree
Hide file tree
Showing 7 changed files with 24 additions and 16 deletions.
10 changes: 9 additions & 1 deletion data-raw/generate_biomee_driver_data.R
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,8 @@ params_soil <- tibble(
)

init_cohort <- tibble(
init_cohort_species = rep(1, 10), # indicates sps # 1 - Fagus sylvatica
init_n_cohorts = 2, # number of PFTs: 1,2,...
init_cohort_species = rep(1, 10), # indicates sps #1 - Fagus sylvatica
init_cohort_nindivs = rep(0.05,10), # initial individual density, individual/m2 ! 1 indiv/m2 = 10.000 indiv/ha
init_cohort_bl = rep(0.0,10), # initial biomass of leaves, kg C/individual
init_cohort_br = rep(0.0, 10), # initial biomass of fine roots, kg C/individual
Expand Down Expand Up @@ -286,6 +287,13 @@ cowplot::plot_grid(
theme_classic()+labs(x = "Year", y = "plantC")
)

biomee_p_model_output_annual_cohorts %>% group_by(PFT,year) %>%
summarise(sumBA=sum(DBH*DBH*pi/4*density/10000)) %>% mutate(PFT=as.factor(PFT)) %>%
ggplot() +
geom_line(aes(x = year, y = sumBA,col=PFT)) +
theme_classic()+labs(x = "Year", y = "BA") +
scale_colour_discrete(labels = c("Grass","Broadleaf","Needleleaf1","Needleleaf2"))

save(biomee_p_model_output,
file = "data/biomee_p_model_output.rda",
compress = "xz")
Expand Down
Binary file modified data/biomee_gs_leuning_drivers.rda
Binary file not shown.
Binary file modified data/biomee_p_model_drivers.rda
Binary file not shown.
2 changes: 1 addition & 1 deletion src/datatypes.mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -528,7 +528,7 @@ module datatypes

!=============== Initial cohort specifications in R ============================================
! Initial values passed through R
integer :: init_n_cohorts = MAX_INIT_COHORTS
! integer :: init_n_cohorts = MAX_INIT_COHORTS
! integer :: init_cohort_species(MAX_INIT_COHORTS) = 2
! real :: init_cohort_nindivs(MAX_INIT_COHORTS) = 1.0 ! initial individual density, individual/m2
! real :: init_cohort_bl(MAX_INIT_COHORTS) = 0.0 ! initial biomass of leaves, kg C/individual
Expand Down
3 changes: 2 additions & 1 deletion src/interface_biosphere_biomee.mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,8 @@ module md_interface_biomee
end type paramstype_species

type inittype_cohort
real :: init_cohort_species
integer :: init_n_cohorts
integer :: init_cohort_species
real :: init_cohort_nindivs
real :: init_cohort_bl
real :: init_cohort_br
Expand Down
21 changes: 10 additions & 11 deletions src/sofun_r.f90
Original file line number Diff line number Diff line change
Expand Up @@ -405,7 +405,7 @@ subroutine biomee_f( &
! naked arrays
real(kind=c_double), dimension(0:MSPECIES,55), intent(in) :: params_species
real(kind=c_double), dimension(n_dim_soil_types,8), intent(in) :: params_soil
real(kind=c_double), dimension(MAX_INIT_COHORTS,8), intent(in) :: init_cohort
real(kind=c_double), dimension(MAX_INIT_COHORTS,9), intent(in) :: init_cohort

! initial soil pool size
real(kind=c_double), intent(in) :: init_fast_soil_C
Expand Down Expand Up @@ -630,17 +630,16 @@ subroutine biomee_f( &
myinterface%params_species(:)%phiRL = real( params_species(:,54)) ! calibratable
myinterface%params_species(:)%LAI_light = real( params_species(:,55)) ! calibratable



! Initial cohort sizes
myinterface%init_cohort(:)%init_cohort_species = int(init_cohort(:,1))
myinterface%init_cohort(:)%init_cohort_nindivs = real(init_cohort(:,2))
myinterface%init_cohort(:)%init_cohort_bl = real(init_cohort(:,3))
myinterface%init_cohort(:)%init_cohort_br = real(init_cohort(:,4))
myinterface%init_cohort(:)%init_cohort_bsw = real(init_cohort(:,5))
myinterface%init_cohort(:)%init_cohort_bHW = real(init_cohort(:,6))
myinterface%init_cohort(:)%init_cohort_seedC = real(init_cohort(:,7))
myinterface%init_cohort(:)%init_cohort_nsc = real(init_cohort(:,8))
myinterface%init_cohort(:)%init_n_cohorts = int(init_cohort(:,1))
myinterface%init_cohort(:)%init_cohort_species = int(init_cohort(:,2))
myinterface%init_cohort(:)%init_cohort_nindivs = real(init_cohort(:,3))
myinterface%init_cohort(:)%init_cohort_bl = real(init_cohort(:,4))
myinterface%init_cohort(:)%init_cohort_br = real(init_cohort(:,5))
myinterface%init_cohort(:)%init_cohort_bsw = real(init_cohort(:,6))
myinterface%init_cohort(:)%init_cohort_bHW = real(init_cohort(:,7))
myinterface%init_cohort(:)%init_cohort_seedC = real(init_cohort(:,8))
myinterface%init_cohort(:)%init_cohort_nsc = real(init_cohort(:,9))

! Initial soil pools
myinterface%init_soil%init_fast_soil_C = real( init_fast_soil_C )
Expand Down
4 changes: 2 additions & 2 deletions src/vegetation_biomee.mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2235,7 +2235,7 @@ subroutine initialize_vegn_tile( vegn, nCohorts )
integer,parameter :: rand_seed = 86456
real :: r
real :: btotal
integer :: i, istat
integer :: i, istat, init_n_cohorts
! integer :: io ! i/o status for the namelist
! integer :: ierr ! error code, returned by i/o routines
! integer :: nml_unit
Expand Down Expand Up @@ -2265,7 +2265,7 @@ subroutine initialize_vegn_tile( vegn, nCohorts )
if (read_from_parameter_file) then

! Initialize plant cohorts
init_n_cohorts = nCohorts ! Weng,2018-11-21
init_n_cohorts = myinterface%init_cohort(1)%init_n_cohorts !nCohorts !Weng,2018-11-21
allocate(cc(1:init_n_cohorts), STAT = istat)
vegn%cohorts => cc
vegn%n_cohorts = init_n_cohorts
Expand Down

0 comments on commit 73be8fa

Please sign in to comment.