Skip to content

Commit d554ed4

Browse files
authored
Merge pull request #1262 from rgknox/leaf_funcunit_tests
leaf biophysics refactor and functional unit tests
2 parents fb92517 + 82ece1f commit d554ed4

24 files changed

+4858
-1687
lines changed

biogeochem/EDPhysiologyMod.F90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ module EDPhysiologyMod
4747
use EDCohortDynamicsMod , only : InitPRTObject
4848
use FatesAllometryMod , only : tree_lai_sai
4949
use FatesAllometryMod , only : leafc_from_treelai
50-
use FatesAllometryMod , only : decay_coeff_vcmax
50+
use LeafBiophysicsMod , only : DecayCoeffVcmax
5151
use FatesLitterMod , only : litter_type
5252
use EDTypesMod , only : site_massbal_type
5353
use EDTypesMod , only : numlevsoil_max
@@ -765,7 +765,7 @@ subroutine trim_canopy( currentSite )
765765

766766
! Calculate sla_levleaf following the sla profile with overlying leaf area
767767
! Scale for leaf nitrogen profile
768-
kn = decay_coeff_vcmax(currentCohort%vcmax25top, &
768+
kn = DecayCoeffVcmax(currentCohort%vcmax25top, &
769769
prt_params%leafn_vert_scaler_coeff1(ipft), &
770770
prt_params%leafn_vert_scaler_coeff2(ipft))
771771

biogeochem/FatesAllometryMod.F90

Lines changed: 8 additions & 44 deletions
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,8 @@ module FatesAllometryMod
100100
use FatesGlobals , only : FatesWarn,N2S,A2S,I2S
101101
use EDParamsMod , only : nlevleaf,dinc_vai,dlower_vai
102102
use DamageMainMod , only : GetCrownReduction
103-
103+
use LeafBiophysicsMod, only : DecayCoeffVcmax
104+
104105
implicit none
105106

106107
private
@@ -116,7 +117,6 @@ module FatesAllometryMod
116117
public :: bdead_allom ! Generic bdead wrapper
117118
public :: carea_allom ! Generic crown area wrapper
118119
public :: bstore_allom ! Generic maximum storage carbon wrapper
119-
public :: decay_coeff_vcmax ! vertical canopy decay rate, scaled on vcmax
120120
public :: ForceDBH ! Method to set DBH to sync with structure
121121
! or fineroot biomass
122122
public :: CheckIntegratedAllometries
@@ -717,9 +717,9 @@ real(r8) function tree_lai( leaf_c, pft, c_area, nplant, cl, canopy_lai, vcmax25
717717
end if
718718

719719
! Coefficient for exponential decay of 1/sla with canopy depth:
720-
kn = decay_coeff_vcmax(vcmax25top, &
721-
prt_params%leafn_vert_scaler_coeff1(pft), &
722-
prt_params%leafn_vert_scaler_coeff2(pft))
720+
kn = DecayCoeffVcmax(vcmax25top, &
721+
prt_params%leafn_vert_scaler_coeff1(pft), &
722+
prt_params%leafn_vert_scaler_coeff2(pft))
723723

724724
! take PFT-level maximum SLA value, even if under a thick canopy (which has units of m2/gC),
725725
! and put into units of m2/kgC
@@ -940,9 +940,9 @@ real(r8) function leafc_from_treelai( treelai, treesai, pft, c_area, nplant, cl,
940940
sla_max = g_per_kg * prt_params%slamax(pft)
941941

942942
! Coefficient for exponential decay of 1/sla with canopy depth:
943-
kn = decay_coeff_vcmax(vcmax25top, &
944-
prt_params%leafn_vert_scaler_coeff1(pft), &
945-
prt_params%leafn_vert_scaler_coeff2(pft))
943+
kn = DecayCoeffVcmax(vcmax25top, &
944+
prt_params%leafn_vert_scaler_coeff1(pft), &
945+
prt_params%leafn_vert_scaler_coeff2(pft))
946946

947947
if(treelai > 0.0_r8)then
948948
! Leafc_per_unitarea at which sla_max is reached due to exponential sla profile in canopy:
@@ -2979,42 +2979,6 @@ end subroutine jackson_beta_root_profile
29792979
! =====================================================================================
29802980

29812981

2982-
real(r8) function decay_coeff_vcmax(vcmax25top,slope_param,intercept_param)
2983-
2984-
! ---------------------------------------------------------------------------------
2985-
! This function estimates the decay coefficient used to estimate vertical
2986-
! attenuation of properties in the canopy.
2987-
!
2988-
! Decay coefficient (kn) is a function of vcmax25top for each pft.
2989-
!
2990-
! Currently, this decay is applied to vcmax attenuation, SLA (optionally)
2991-
! and leaf respiration (optionally w/ Atkin)
2992-
!
2993-
! ---------------------------------------------------------------------------------
2994-
2995-
!ARGUMENTS
2996-
2997-
real(r8),intent(in) :: vcmax25top
2998-
real(r8),intent(in) :: slope_param ! multiplies vcmax25top
2999-
real(r8),intent(in) :: intercept_param ! adds to vcmax25top
3000-
3001-
3002-
!LOCAL VARIABLES
3003-
! -----------------------------------------------------------------------------------
3004-
3005-
! Bonan et al (2011) JGR, 116, doi:10.1029/2010JG001593 used
3006-
! kn = 0.11. Here, we derive kn from vcmax25 as in Lloyd et al
3007-
! (2010) Biogeosciences, 7, 1833-1859
3008-
! This function is also used to vertically scale leaf maintenance
3009-
! respiration.
3010-
3011-
decay_coeff_vcmax = exp(slope_param * vcmax25top - intercept_param)
3012-
3013-
return
3014-
end function decay_coeff_vcmax
3015-
3016-
! =====================================================================================
3017-
30182982
subroutine ForceDBH( ipft, crowndamage, canopy_trim, elongf_leaf, elongf_stem, d, h, bdead, bl )
30192983

30202984
! =========================================================================
Lines changed: 260 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,260 @@
1+
module FatesLeafBiophysParamsMod
2+
3+
use FatesConstantsMod , only: r8 => fates_r8
4+
use FatesConstantsMod , only: fates_check_param_set
5+
use FatesParametersInterface, only : param_string_length
6+
use FatesGlobals, only : fates_log
7+
use FatesGlobals, only : endrun => fates_endrun
8+
use shr_log_mod , only : errMsg => shr_log_errMsg
9+
use LeafBiophysicsMod, only : lb_params,btran_on_gs_gs1,btran_on_ag_none
10+
use FatesParametersInterface, only : fates_parameters_type
11+
! Register the parameters we want the host to provide, and
12+
! indicate whether they are fates parameters or host parameters
13+
! that need to be synced with host values.
14+
use FatesParametersInterface, only : fates_parameters_type, param_string_length
15+
use FatesParametersInterface, only : dimension_name_pft, dimension_shape_1d
16+
use FatesParametersInterface, only : dimension_shape_scalar, dimension_name_scalar
17+
use FatesUtilsMod, only : ArrayNint
18+
19+
implicit none
20+
private ! Modules are private by default
21+
save
22+
23+
public :: LeafBiophysRegisterParams
24+
public :: LeafBiophysReceiveParams
25+
public :: LeafBiophysReportParams
26+
27+
character(len=*), parameter :: sourcefile = &
28+
__FILE__
29+
30+
integer, parameter :: lower_bound_pft = 1
31+
32+
contains
33+
34+
! =====================================================================================
35+
36+
subroutine LeafBiophysRegisterParams(fates_params)
37+
38+
39+
class(fates_parameters_type), intent(inout) :: fates_params
40+
41+
character(len=param_string_length), parameter :: dim_names(1) = (/dimension_name_pft/)
42+
integer, parameter :: dim_lower_bound(1) = (/ lower_bound_pft /)
43+
character(len=param_string_length) :: name
44+
character(len=param_string_length), parameter :: dim_names_scalar(1) = (/dimension_name_scalar/)
45+
46+
47+
! Register PFT dimensioned
48+
49+
name = 'fates_leaf_c3psn'
50+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
51+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
52+
53+
name = 'fates_leaf_stomatal_btran_model'
54+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
55+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
56+
57+
name = 'fates_leaf_agross_btran_model'
58+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
59+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
60+
61+
name = 'fates_leaf_stomatal_slope_ballberry'
62+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
63+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
64+
65+
name = 'fates_leaf_stomatal_slope_medlyn'
66+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
67+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
68+
69+
name = 'fates_leaf_stomatal_intercept'
70+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
71+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
72+
73+
name = 'fates_maintresp_reduction_curvature'
74+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
75+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
76+
77+
name = 'fates_maintresp_reduction_intercept'
78+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
79+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
80+
81+
name = 'fates_maintresp_reduction_upthresh'
82+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
83+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
84+
85+
name = 'fates_maintresp_leaf_atkin2017_baserate'
86+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
87+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
88+
89+
name = 'fates_maintresp_leaf_ryan1991_baserate'
90+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
91+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
92+
93+
name = 'fates_leaf_vcmaxha'
94+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
95+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
96+
97+
name = 'fates_leaf_jmaxha'
98+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
99+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
100+
101+
name = 'fates_leaf_vcmaxhd'
102+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
103+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
104+
105+
name = 'fates_leaf_jmaxhd'
106+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
107+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
108+
109+
name = 'fates_leaf_vcmaxse'
110+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
111+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
112+
113+
name = 'fates_leaf_jmaxse'
114+
call fates_params%RegisterParameter(name=name, dimension_shape=dimension_shape_1d, &
115+
dimension_names=dim_names, lower_bounds=dim_lower_bound)
116+
117+
return
118+
end subroutine LeafBiophysRegisterParams
119+
120+
! =====================================================================================
121+
122+
subroutine LeafBiophysReceiveParams(fates_params)
123+
124+
!use FatesInterfaceTypesMod, only : hlm_daylength_factor_switch
125+
!use FatesInterfaceTypesMod, only : hlm_stomatal_model
126+
!use FatesInterfaceTypesMod, only : hlm_stomatal_assim_model
127+
!use FatesInterfaceTypesMod, only : hlm_photo_tempsens_model
128+
129+
class(fates_parameters_type), intent(inout) :: fates_params
130+
real(r8), allocatable :: tmpreal(:) ! Temporary variable to hold floats
131+
real(r8) :: tmpscalar
132+
character(len=param_string_length) :: name
133+
134+
!lb_params%dayl_switch = hlm_daylength_factor_switch
135+
!lb_params%stomatal_model = hlm_stomatal_model
136+
!lb_params%stomatal_assim_model = hlm_stomatal_assim_model
137+
!lb_params%photo_tempsens_model = hlm_photo_tempsens_model
138+
139+
name = 'fates_leaf_c3psn'
140+
call fates_params%RetrieveParameterAllocate(name=name, &
141+
data=tmpreal)
142+
allocate(lb_params%c3psn(size(tmpreal,dim=1)))
143+
call ArrayNint(tmpreal,lb_params%c3psn)
144+
deallocate(tmpreal)
145+
146+
name = 'fates_leaf_stomatal_btran_model'
147+
call fates_params%RetrieveParameterAllocate(name=name, &
148+
data=tmpreal)
149+
allocate(lb_params%stomatal_btran_model(size(tmpreal,dim=1)))
150+
call ArrayNint(tmpreal,lb_params%stomatal_btran_model)
151+
deallocate(tmpreal)
152+
153+
name = 'fates_leaf_agross_btran_model'
154+
call fates_params%RetrieveParameterAllocate(name=name, &
155+
data=tmpreal)
156+
allocate(lb_params%agross_btran_model(size(tmpreal,dim=1)))
157+
call ArrayNint(tmpreal,lb_params%agross_btran_model)
158+
deallocate(tmpreal)
159+
160+
name = 'fates_leaf_stomatal_slope_medlyn'
161+
call fates_params%RetrieveParameterAllocate(name=name, &
162+
data=lb_params%medlyn_slope)
163+
164+
name = 'fates_leaf_stomatal_slope_ballberry'
165+
call fates_params%RetrieveParameterAllocate(name=name, &
166+
data=lb_params%bb_slope)
167+
168+
name = 'fates_leaf_stomatal_intercept'
169+
call fates_params%RetrieveParameterAllocate(name=name, &
170+
data=lb_params%stomatal_intercept)
171+
172+
name = 'fates_maintresp_leaf_ryan1991_baserate'
173+
call fates_params%RetrieveParameterAllocate(name=name, &
174+
data=lb_params%maintresp_leaf_ryan1991_baserate)
175+
176+
name = 'fates_maintresp_leaf_atkin2017_baserate'
177+
call fates_params%RetrieveParameterAllocate(name=name, &
178+
data=lb_params%maintresp_leaf_atkin2017_baserate)
179+
180+
name = 'fates_maintresp_reduction_curvature'
181+
call fates_params%RetrieveParameterAllocate(name=name, &
182+
data=lb_params%maintresp_reduction_curvature)
183+
184+
name = 'fates_maintresp_reduction_intercept'
185+
call fates_params%RetrieveParameterAllocate(name=name, &
186+
data=lb_params%maintresp_reduction_intercept)
187+
188+
name = 'fates_maintresp_reduction_upthresh'
189+
call fates_params%RetrieveParameterAllocate(name=name, &
190+
data=lb_params%maintresp_reduction_upthresh)
191+
192+
name = 'fates_leaf_vcmaxha'
193+
call fates_params%RetrieveParameterAllocate(name=name, &
194+
data=lb_params%vcmaxha)
195+
196+
name = 'fates_leaf_jmaxha'
197+
call fates_params%RetrieveParameterAllocate(name=name, &
198+
data=lb_params%jmaxha)
199+
200+
name = 'fates_leaf_vcmaxhd'
201+
call fates_params%RetrieveParameterAllocate(name=name, &
202+
data=lb_params%vcmaxhd)
203+
204+
name = 'fates_leaf_jmaxhd'
205+
call fates_params%RetrieveParameterAllocate(name=name, &
206+
data=lb_params%jmaxhd)
207+
208+
name = 'fates_leaf_vcmaxse'
209+
call fates_params%RetrieveParameterAllocate(name=name, &
210+
data=lb_params%vcmaxse)
211+
212+
name = 'fates_leaf_jmaxse'
213+
call fates_params%RetrieveParameterAllocate(name=name, &
214+
data=lb_params%jmaxse)
215+
216+
217+
return
218+
end subroutine LeafBiophysReceiveParams
219+
220+
! ====================================================================================
221+
222+
subroutine LeafBiophysReportParams(is_master)
223+
224+
! Argument
225+
logical, intent(in) :: is_master ! Only log if this is the master proc
226+
227+
logical, parameter :: debug_report = .false.
228+
character(len=32),parameter :: fmt_rout = '(a,F16.8)'
229+
character(len=32),parameter :: fmt_iout = '(a,I8)'
230+
231+
integer :: npft,ipft
232+
233+
if(debug_report .and. is_master) then
234+
write(fates_log(),fmt_iout) 'fates_leaf_c3psn = ',lb_params%c3psn
235+
write(fates_log(),fmt_iout) 'fates_leaf_stomatal_btran_model = ',lb_params%stomatal_btran_model
236+
write(fates_log(),fmt_iout) 'fates_leaf_agross_btran_model = ',lb_params%agross_btran_model
237+
write(fates_log(),fmt_rout) 'fates_leaf_vcmaxha = ',lb_params%vcmaxha
238+
write(fates_log(),fmt_rout) 'fates_leaf_jmaxha = ',lb_params%jmaxha
239+
write(fates_log(),fmt_rout) 'fates_leaf_vcmaxhd = ',lb_params%vcmaxhd
240+
write(fates_log(),fmt_rout) 'fates_leaf_jmaxhd = ',lb_params%jmaxhd
241+
write(fates_log(),fmt_rout) 'fates_leaf_vcmaxse = ',lb_params%vcmaxse
242+
write(fates_log(),fmt_rout) 'fates_leaf_jmaxse = ',lb_params%jmaxse
243+
write(fates_log(),fmt_iout) 'fates_daylength_factor_switch = ',lb_params%dayl_switch
244+
write(fates_log(),fmt_iout) 'fates_leaf_stomatal_model = ',lb_params%stomatal_model
245+
write(fates_log(),fmt_iout) 'fates_leaf_stomatal_assim_model = ',lb_params%stomatal_assim_model
246+
write(fates_log(),fmt_iout) 'fates_leaf_photo_tempsens_model = ',lb_params%photo_tempsens_model
247+
write(fates_log(),fmt_rout) 'fates_leaf_stomatal_slope_medlyn = ',lb_params%medlyn_slope
248+
write(fates_log(),fmt_rout) 'fates_leaf_stomatal_slope_ballberry = ',lb_params%bb_slope
249+
write(fates_log(),fmt_rout) 'fates_leaf_stomatal_intercept = ',lb_params%stomatal_intercept
250+
write(fates_log(),fmt_rout) 'fates_maintresp_leaf_ryan1991_baserate = ',lb_params%maintresp_leaf_ryan1991_baserate
251+
write(fates_log(),fmt_rout) 'fates_maintresp_leaf_atkin2017_baserate = ',lb_params%maintresp_leaf_atkin2017_baserate
252+
write(fates_log(),fmt_rout) 'fates_maintresp_reduction_curvature = ',lb_params%maintresp_reduction_curvature
253+
write(fates_log(),fmt_rout) 'fates_maintresp_reduction_intercept = ',lb_params%maintresp_reduction_intercept
254+
write(fates_log(),fmt_rout) 'fates_maintresp_reduction_upthresh = ',lb_params%maintresp_reduction_upthresh
255+
end if
256+
257+
258+
end subroutine LeafBiophysReportParams
259+
260+
end module FatesLeafBiophysParamsMod

0 commit comments

Comments
 (0)