Skip to content

Commit

Permalink
move radiation model switch from EDParamsMod to FatesInterfaceTypesMod
Browse files Browse the repository at this point in the history
  • Loading branch information
glemieux committed Dec 12, 2024
1 parent 1056092 commit c8e0d2b
Show file tree
Hide file tree
Showing 8 changed files with 30 additions and 44 deletions.
10 changes: 5 additions & 5 deletions biogeochem/EDCanopyStructureMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,6 @@ module EDCanopyStructureMod
use FatesCohortMod, only : fates_cohort_type
use EDParamsMod , only : nclmax
use EDParamsMod , only : nlevleaf
use EDParamsMod , only : radiation_model
use EDtypesMod , only : AREA
use EDLoggingMortalityMod , only : UpdateHarvestC
use FatesGlobals , only : endrun => fates_endrun
Expand Down Expand Up @@ -1314,11 +1313,12 @@ subroutine canopy_summarization( nsites, sites, bc_in )
! ---------------------------------------------------------------------------------

use FatesInterfaceTypesMod , only : hlm_use_cohort_age_tracking
use EDPatchDynamicsMod , only : set_patchno
use FatesInterfaceTypesMod , only : hlm_radiation_model
use EDPatchDynamicsMod , only : set_patchno
use FatesSizeAgeTypeIndicesMod, only : sizetype_class_index
use FatesSizeAgeTypeIndicesMod, only : coagetype_class_index
use EDtypesMod , only : area
use FatesConstantsMod , only : itrue
use EDtypesMod , only : area
use FatesConstantsMod , only : itrue

! !ARGUMENTS
integer , intent(in) :: nsites
Expand Down Expand Up @@ -1452,7 +1452,7 @@ subroutine canopy_summarization( nsites, sites, bc_in )

call leaf_area_profile(sites(s))

if(radiation_model.eq.twostr_solver) then
if(hlm_radiation_model.eq.twostr_solver) then
call FatesConstructRadElements(sites(s),bc_in(s)%fcansno_pa,bc_in(s)%coszen_pa)
end if

Expand Down
8 changes: 4 additions & 4 deletions biogeophys/FatesPlantRespPhotosynthMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,6 @@ module FATESPlantRespPhotosynthMod
use EDPftvarcon , only : EDPftvarcon_inst
use TemperatureType, only : temperature_type
use FatesRadiationMemMod, only : norman_solver,twostr_solver
use EDParamsMod, only : radiation_model
use FatesRadiationMemMod, only : ipar
use FatesTwoStreamUtilsMod, only : FatesGetCohortAbsRad
use FatesAllometryMod , only : VegAreaLayer
Expand Down Expand Up @@ -149,6 +148,7 @@ subroutine FatesPlantRespPhotosynthDrive (nsites, sites,bc_in,bc_out,dtime)
use DamageMainMod, only : GetCrownReduction

use FatesInterfaceTypesMod, only : hlm_use_tree_damage
use FatesInterfaceTypesMod, only : hlm_radiation_model

! ARGUMENTS:
! -----------------------------------------------------------------------------------
Expand Down Expand Up @@ -496,7 +496,7 @@ subroutine FatesPlantRespPhotosynthDrive (nsites, sites,bc_in,bc_out,dtime)

rate_mask_if: if ( .not.rate_mask_z(iv,ft,cl) .or. &
(hlm_use_planthydro.eq.itrue) .or. &
(radiation_model .eq. twostr_solver ) .or. &
(hlm_radiation_model .eq. twostr_solver ) .or. &
(nleafage > 1) .or. &
(hlm_parteh_mode .ne. prt_carbon_allom_hyp ) ) then

Expand Down Expand Up @@ -621,7 +621,7 @@ subroutine FatesPlantRespPhotosynthDrive (nsites, sites,bc_in,bc_out,dtime)
! as large as the layer above.
! ------------------------------------------------------------------

if_radsolver: if(radiation_model.eq.norman_solver) then
if_radsolver: if(hlm_radiation_model.eq.norman_solver) then

laisun = currentPatch%ed_laisun_z(cl,ft,iv)
laisha = currentPatch%ed_laisha_z(cl,ft,iv)
Expand Down Expand Up @@ -752,7 +752,7 @@ subroutine FatesPlantRespPhotosynthDrive (nsites, sites,bc_in,bc_out,dtime)
nv = currentCohort%nv

! Temporary bypass to preserve B4B behavior
if(radiation_model.eq.norman_solver) then
if(hlm_radiation_model.eq.norman_solver) then

call ScaleLeafLayerFluxToCohort(nv, & !in
psn_z(1:nv,ft,cl), & !in
Expand Down
11 changes: 0 additions & 11 deletions main/EDParamsMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -43,8 +43,6 @@ module EDParamsMod
real(r8),protected, public :: sdlng2sap_par_timescale !Length of the window for the exponential
!moving average of par at the seedling layer used to
!calculate seedling to sapling transition rates
integer,protected, public :: radiation_model ! Switch betrween Norman (1) and Two-stream (2) radiation models

real(r8),protected, public :: fates_mortality_disturbance_fraction ! the fraction of canopy mortality that results in disturbance
real(r8),protected, public :: ED_val_comp_excln ! weighting factor for canopy layer exclusion and promotion
real(r8),protected, public :: ED_val_vai_top_bin_width ! width in VAI units of uppermost leaf+stem layer scattering element
Expand Down Expand Up @@ -131,7 +129,6 @@ module EDParamsMod
integer, protected,allocatable,public :: hydr_htftype_node(:)
character(len=param_string_length),parameter,public :: ED_name_photo_temp_acclim_timescale = "fates_leaf_photo_temp_acclim_timescale"
character(len=param_string_length),parameter,public :: ED_name_photo_temp_acclim_thome_time = "fates_leaf_photo_temp_acclim_thome_time"
character(len=param_string_length),parameter,public :: name_radiation_model = "fates_rad_model"
character(len=param_string_length),parameter,public :: ED_name_hydr_htftype_node = "fates_hydro_htftype_node"
character(len=param_string_length),parameter,public :: ED_name_mort_disturb_frac = "fates_mort_disturb_frac"
character(len=param_string_length),parameter,public :: ED_name_comp_excln = "fates_comp_excln"
Expand Down Expand Up @@ -286,7 +283,6 @@ subroutine FatesParamsInit()
sdlng_mdd_timescale = nan
sdlng2sap_par_timescale = nan
photo_temp_acclim_thome_time = nan
radiation_model = -9
fates_mortality_disturbance_fraction = nan
ED_val_comp_excln = nan
ED_val_vai_top_bin_width = nan
Expand Down Expand Up @@ -378,9 +374,6 @@ subroutine FatesRegisterParams(fates_params)
call fates_params%RegisterParameter(name=ED_name_photo_temp_acclim_thome_time, dimension_shape=dimension_shape_scalar, &
dimension_names=dim_names_scalar)

call fates_params%RegisterParameter(name=name_radiation_model,dimension_shape=dimension_shape_scalar, &
dimension_names=dim_names_scalar)

call fates_params%RegisterParameter(name=name_theta_cj_c3, dimension_shape=dimension_shape_scalar, &
dimension_names=dim_names_scalar)

Expand Down Expand Up @@ -585,10 +578,6 @@ subroutine FatesReceiveParams(fates_params)
call fates_params%RetrieveParameter(name=ED_name_photo_temp_acclim_thome_time, &
data=photo_temp_acclim_thome_time)

call fates_params%RetrieveParameter(name=name_radiation_model, &
data=tmpreal)
radiation_model = nint(tmpreal)

call fates_params%RetrieveParameter(name=ED_name_mort_disturb_frac, &
data=fates_mortality_disturbance_fraction)

Expand Down
18 changes: 0 additions & 18 deletions main/EDPftvarcon.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1827,7 +1827,6 @@ subroutine FatesCheckParams(is_master)
use FatesConstantsMod, only : lmr_r_2
use EDParamsMod , only : logging_mechanical_frac, logging_collateral_frac
use EDParamsMod , only : logging_direct_frac,logging_export_frac
use EDParamsMod , only : radiation_model, dayl_switch
use FatesInterfaceTypesMod, only : hlm_use_fixed_biogeog,hlm_use_sp, hlm_name
use FatesInterfaceTypesMod, only : hlm_use_inventory_init
use FatesInterfaceTypesMod, only : hlm_use_nocomp
Expand Down Expand Up @@ -1858,15 +1857,6 @@ subroutine FatesCheckParams(is_master)

if(.not.is_master) return

if(.not.any(radiation_model == [norman_solver,twostr_solver])) then
write(fates_log(),*) 'The only available canopy radiation models'
write(fates_log(),*) 'are the Norman and Two-stream schemes, '
write(fates_log(),*) 'fates_rad_model = 1 or 2 ...'
write(fates_log(),*) 'You specified fates_rad_model = ',radiation_model
write(fates_log(),*) 'Aborting'
call endrun(msg=errMsg(sourcefile, __LINE__))
end if

if(.not.any(regeneration_model == [default_regeneration, &
TRS_regeneration, &
TRS_no_seedling_dyn] )) then
Expand All @@ -1877,14 +1867,6 @@ subroutine FatesCheckParams(is_master)
call endrun(msg=errMsg(sourcefile, __LINE__))
end if

if(.not.any(dayl_switch == [itrue,ifalse])) then
write(fates_log(),*) 'The only valid switch options for '
write(fates_log(),*) 'fates_daylength_factor_switch is 0 or 1 ...'
write(fates_log(),*) 'You specified fates_daylength_factor_switch = ',dayl_switch
write(fates_log(),*) 'Aborting'
call endrun(msg=errMsg(sourcefile, __LINE__))
end if

select case (hlm_parteh_mode)
case (prt_cnp_flex_allom_hyp)

Expand Down
12 changes: 12 additions & 0 deletions main/FatesInterfaceMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -1481,6 +1481,7 @@ subroutine set_fates_ctrlparms(tag,ival,rval,cval)
hlm_hydr_solver = unset_int
hlm_maintresp_leaf_model = unset_int
hlm_mort_cstarvation_model = unset_int
hlm_radiation_model = unset_int
hlm_use_logging = unset_int
hlm_use_ed_st3 = unset_int
hlm_use_ed_prescribed_phys = unset_int
Expand Down Expand Up @@ -1800,6 +1801,11 @@ subroutine set_fates_ctrlparms(tag,ival,rval,cval)
call endrun(msg=errMsg(sourcefile, __LINE__))
end if

if(hlm_radiation_model .eq. unset_int) then
write(fates_log(), *) 'radiation model is unset: hlm_radiation_model exiting'
call endrun(msg=errMsg(sourcefile, __LINE__))
end if

if(hlm_use_sp.eq.itrue.and.hlm_use_nocomp.eq.ifalse)then
write(fates_log(), *) 'SP cannot be on if nocomp mode is off. Exiting. '
call endrun(msg=errMsg(sourcefile, __LINE__))
Expand Down Expand Up @@ -2045,6 +2051,12 @@ subroutine set_fates_ctrlparms(tag,ival,rval,cval)
write(fates_log(),*) 'Transfering hlm_mort_cstarvation_model ',ival,' to FATES'
end if

case('radiation_model')
hlm_radiation_model = ival
if (fates_global_verbose()) then
write(fates_log(),*) 'Transfering hlm_radiation_model ',ival,' to FATES'
end if

case('use_logging')
hlm_use_logging = ival
if (fates_global_verbose()) then
Expand Down
3 changes: 3 additions & 0 deletions main/FatesInterfaceTypesMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -186,6 +186,9 @@ module FatesInterfaceTypesMod
! 1 -- Linear model
! 2 -- Exponential model

integer, public :: hlm_radiation_model ! Switch for radiation model
! Norman (1) and Two-stream (2)

integer, public :: hlm_use_ed_st3 ! This flag signals whether or not to use
! (ST)atic (ST)and (ST)ructure mode (ST3)
! Essentially, this gives us the ability
Expand Down
4 changes: 2 additions & 2 deletions main/FatesRestartInterfaceMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ module FatesRestartInterfaceMod
use FatesPlantHydraulicsMod, only : InitHydrCohort
use FatesInterfaceTypesMod, only : nlevsclass
use FatesInterfaceTypesMod, only : nlevdamage
use FatesInterfaceTypesMod, only : hlm_radiation_model
use FatesLitterMod, only : litter_type
use FatesLitterMod, only : ncwd
use FatesFuelClassesMod, only : num_fuel_classes
Expand All @@ -52,7 +53,6 @@ module FatesRestartInterfaceMod
use FatesRadiationMemMod, only : num_swb,norman_solver,twostr_solver
use TwoStreamMLPEMod, only : normalized_upper_boundary
use EDParamsMod, only : regeneration_model
use EDParamsMod, only : radiation_model
use FatesConstantsMod, only : n_term_mort_types
use FatesConstantsMod, only : n_landuse_cats
use FatesConstantsMod, only : N_DIST_TYPES
Expand Down Expand Up @@ -3868,7 +3868,7 @@ subroutine update_3dpatch_radiation(this, nsites, sites, bc_out)
enddo
else

select case(radiation_model)
select case(hlm_radiation_model)
case(norman_solver)

call PatchNormanRadiation (currentPatch, &
Expand Down
8 changes: 4 additions & 4 deletions radiation/FatesRadiationDriveMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,13 @@ module FatesRadiationDriveMod
use FatesInterfaceTypesMod , only : bc_in_type
use FatesInterfaceTypesMod , only : bc_out_type
use FatesInterfaceTypesMod , only : numpft
use FatesInterfaceTypesMod , only : hlm_radiation_model
use FatesRadiationMemMod, only : num_rad_stream_types
use FatesRadiationMemMod, only : idirect, idiffuse
use FatesRadiationMemMod, only : num_swb, ivis, inir, ipar
use FatesRadiationMemMod, only : alb_ice, rho_snow, tau_snow
use FatesRadiationMemMod, only : norman_solver
use FatesRadiationMemMod, only : twostr_solver
use EDParamsMod, only : radiation_model
use TwoStreamMLPEMod, only : normalized_upper_boundary
use FatesTwoStreamUtilsMod, only : FatesPatchFSun
use FatesTwoStreamUtilsMod, only : CheckPatchRadiationBalance
Expand Down Expand Up @@ -128,7 +128,7 @@ subroutine FatesNormalizedCanopyRadiation(nsites, sites, bc_in, bc_out )
currentPatch%gnd_alb_dir(1:num_swb) = bc_in(s)%albgr_dir_rb(1:num_swb)
currentPatch%fcansno = bc_in(s)%fcansno_pa(ifp)

if(radiation_model.eq.twostr_solver) then
if(hlm_radiation_model.eq.twostr_solver) then
call currentPatch%twostr%CanopyPrep(bc_in(s)%fcansno_pa(ifp))
call currentPatch%twostr%ZenithPrep(bc_in(s)%coszen_pa(ifp))
end if
Expand Down Expand Up @@ -177,7 +177,7 @@ subroutine FatesNormalizedCanopyRadiation(nsites, sites, bc_in, bc_out )

else

select case(radiation_model)
select case(hlm_radiation_model)
case(norman_solver)

call PatchNormanRadiation (currentPatch, &
Expand Down Expand Up @@ -312,7 +312,7 @@ subroutine FatesSunShadeFracs(nsites, sites,bc_in,bc_out)

sunlai = 0._r8
shalai = 0._r8
if_norm_twostr: if (radiation_model.eq.norman_solver) then
if_norm_twostr: if (hlm_radiation_model.eq.norman_solver) then

! Loop over patches to calculate laisun_z and laisha_z for each layer.
! Derive canopy laisun, laisha, and fsun from layer sums.
Expand Down

0 comments on commit c8e0d2b

Please sign in to comment.