Skip to content

Commit

Permalink
PPE mods from /glade/work/linnia/PPEn14trans brought to ctsm5.2.015
Browse files Browse the repository at this point in the history
Bringing the diffs between branch_tags/PPE16... and branch_tags/PPE15...
to b4b-dev manually
  • Loading branch information
slevis-lmwg committed Aug 14, 2024
1 parent 15ffb12 commit 4333a66
Show file tree
Hide file tree
Showing 4 changed files with 35 additions and 18 deletions.
8 changes: 0 additions & 8 deletions src/biogeochem/CNFUNMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,6 @@ module CNFUNMod
public:: CNFUN ! Run FUN

type, private :: params_type
real(r8) :: ndays_on ! number of days to complete leaf onset
real(r8) :: ndays_off ! number of days to complete leaf offset
end type params_type

Expand All @@ -64,7 +63,6 @@ module CNFUNMod
!
! !PRIVATE DATA MEMBERS:
real(r8) :: dt ! decomp timestep (seconds)
real(r8) :: ndays_on ! number of days to complete onset
real(r8) :: ndays_off ! number of days to complete offset

integer, private, parameter :: COST_METHOD = 2 !new way of doing the N uptake
Expand Down Expand Up @@ -104,11 +102,6 @@ subroutine readParams ( ncid )

! read in parameters

tString='ndays_on'
call ncd_io(varname=trim(tString),data=tempr, flag='read', ncid=ncid, readvar=readv)
if ( .not. readv ) call endrun( msg=trim(errCode)//trim(tString)//errMsg(sourcefile, __LINE__))
params_inst%ndays_on=tempr

tString='ndays_off'
call ncd_io(varname=trim(tString),data=tempr, flag='read', ncid=ncid, readvar=readv)
if ( .not. readv ) call endrun( msg=trim(errCode)//trim(tString)//errMsg(sourcefile, __LINE__))
Expand Down Expand Up @@ -172,7 +165,6 @@ subroutine CNFUNInit (bounds,cnveg_state_inst,cnveg_carbonstate_inst,cnveg_nitro
timestep_fun = real(secspday * fun_period)
nstep_fun = int(secspday * dayspyr / dt)

ndays_on = params_inst%ndays_on
ndays_off = params_inst%ndays_off

!--------------------------------------------------------------------
Expand Down
23 changes: 13 additions & 10 deletions src/biogeochem/CNPhenologyMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -94,7 +94,6 @@ module CNPhenologyMod
real(r8) :: crit_dayl_lat_slope ! Slope of time for critical day length with latitude (sec/deg)
! (Birch et. all 2021 it was 720 see line below)
! 15hr-11hr/(65N-45N)=linear slope = 720 min/latitude (Birch et. al 2021)
real(r8) :: ndays_on ! number of days to complete leaf onset
real(r8) :: ndays_off ! number of days to complete leaf offset
real(r8) :: fstor2tran ! fraction of storage to move to transfer for each onset
real(r8) :: crit_onset_fdd ! critical number of freezing days to set gdd counter
Expand All @@ -113,7 +112,6 @@ module CNPhenologyMod
real(r8) :: dt ! time step delta t (seconds)
real(r8) :: fracday ! dtime as a fraction of day
real(r8) :: crit_dayl ! critical daylength for offset (seconds)
real(r8) :: ndays_on ! number of days to complete onset
real(r8) :: ndays_off ! number of days to complete offset
real(r8) :: fstor2tran ! fraction of storage to move to transfer on each onset
real(r8) :: crit_onset_fdd ! critical number of freezing days
Expand Down Expand Up @@ -310,7 +308,6 @@ subroutine readParams ( ncid )
call readNcdioScalar(ncid, 'crit_dayl', subname, params_inst%crit_dayl)
call readNcdioScalar(ncid, 'crit_dayl_at_high_lat', subname, params_inst%crit_dayl_at_high_lat)
call readNcdioScalar(ncid, 'crit_dayl_lat_slope', subname, params_inst%crit_dayl_lat_slope)
call readNcdioScalar(ncid, 'ndays_on', subname, params_inst%ndays_on)
call readNcdioScalar(ncid, 'ndays_off', subname, params_inst%ndays_off)
call readNcdioScalar(ncid, 'fstor2tran', subname, params_inst%fstor2tran)
call readNcdioScalar(ncid, 'crit_onset_fdd', subname, params_inst%crit_onset_fdd)
Expand Down Expand Up @@ -471,7 +468,6 @@ subroutine CNPhenologyInit(bounds)
crit_dayl=params_inst%crit_dayl

! Set constants for CNSeasonDecidPhenology and CNStressDecidPhenology
ndays_on=params_inst%ndays_on
ndays_off=params_inst%ndays_off

! set transfer parameters
Expand Down Expand Up @@ -882,6 +878,8 @@ subroutine CNSeasonDecidPhenology (num_soilp, filter_soilp , &
woody => pftcon%woody , & ! Input: binary flag for woody lifeform (1=woody, 0=not woody)
season_decid => pftcon%season_decid , & ! Input: binary flag for seasonal-deciduous leaf habit (0 or 1)
season_decid_temperate => pftcon%season_decid_temperate , & ! Input: binary flag for seasonal-deciduous temperate leaf habit (0 or 1)
crit_onset_gdd_sf => pftcon%crit_onset_gdd_sf , & ! Input: scale factor for crit_onset_gdd (unitless)
ndays_on => pftcon%ndays_on , & ! Input: number of days to complete leaf onset (days

t_soisno => temperature_inst%t_soisno_col , & ! Input: [real(r8) (:,:) ] soil temperature (Kelvin) (-nlevsno+1:nlevgrnd)
soila10 => temperature_inst%soila10_col , & ! Input: [real(r8) (:) ]
Expand Down Expand Up @@ -1016,7 +1014,8 @@ subroutine CNSeasonDecidPhenology (num_soilp, filter_soilp , &
lgsf(p) = 0._r8

! onset gdd sum from Biome-BGC, v4.1.2
crit_onset_gdd = exp(4.8_r8 + 0.13_r8*(annavg_t2m(p) - SHR_CONST_TKFRZ))
crit_onset_gdd = crit_onset_gdd_sf(ivt(p)) * exp(4.8_r8 + 0.13_r8*(annavg_t2m(p) &
- SHR_CONST_TKFRZ))

! set flag for solstice period (winter->summer = 1, summer->winter = 0)
if (dayl(g) >= prev_dayl(g)) then
Expand Down Expand Up @@ -1109,7 +1108,8 @@ subroutine CNSeasonDecidPhenology (num_soilp, filter_soilp , &
onset_gddflag(p) = 0.0_r8
onset_gdd(p) = 0.0_r8
do_onset = .false.
onset_counter(p) = ndays_on * secspday
onset_counter(p) = ndays_on(ivt(p)) * secspday


! move all the storage pools into transfer pools,
! where they will be transfered to displayed growth over the onset period.
Expand Down Expand Up @@ -1399,7 +1399,10 @@ subroutine CNStressDecidPhenology (num_soilp, filter_soilp , &
stress_decid => pftcon%stress_decid , & ! Input: binary flag for stress-deciduous leaf habit (0 or 1)
leafcn => pftcon%leafcn , & ! Input: leaf C:N (gC/gN)
frootcn => pftcon%frootcn , & ! Input: fine root C:N (gC/gN)


crit_onset_gdd_sf => pftcon%crit_onset_gdd_sf , & ! Input: scale factor for crit_onset_gdd (unitless)
ndays_on => pftcon%ndays_on , & ! Input: number of days to complete leaf onset (days)

soilpsi => soilstate_inst%soilpsi_col , & ! Input: [real(r8) (:,:) ] soil water potential in each soil layer (MPa)

t_soisno => temperature_inst%t_soisno_col , & ! Input: [real(r8) (:,:) ] soil temperature (Kelvin) (-nlevsno+1:nlevgrnd)
Expand Down Expand Up @@ -1532,8 +1535,8 @@ subroutine CNStressDecidPhenology (num_soilp, filter_soilp , &
psi = soilpsi(c, phenology_soil_layer)

! onset gdd sum from Biome-BGC, v4.1.2
crit_onset_gdd = exp(4.8_r8 + 0.13_r8*(annavg_t2m(p) - SHR_CONST_TKFRZ))

crit_onset_gdd = crit_onset_gdd_sf(ivt(p)) * exp(4.8_r8 + 0.13_r8*(annavg_t2m(p) &
- SHR_CONST_TKFRZ))

! update offset_counter and test for the end of the offset period
if (offset_flag(p) == 1._r8) then
Expand Down Expand Up @@ -1673,7 +1676,7 @@ subroutine CNStressDecidPhenology (num_soilp, filter_soilp , &
onset_fdd(p) = 0._r8
onset_gdd(p) = 0._r8
onset_swi(p) = 0._r8
onset_counter(p) = ndays_on * secspday
onset_counter(p) = ndays_on(ivt(p)) * secspday

! call subroutine to move all the storage pools into transfer pools,
! where they will be transfered to displayed growth over the onset period.
Expand Down
11 changes: 11 additions & 0 deletions src/main/initVerticalMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,8 @@ module initVerticalMod
type, private :: params_type
real(r8) :: slopebeta ! exponent for microtopography pdf sigma (unitless)
real(r8) :: slopemax ! max topographic slope for microtopography pdf sigma (unitless)
real(r8) :: zbedrock ! parameter to substitute for zbedrock (m)
real(r8) :: zbedrock_sf ! parameter to scale zbedrock (m)
end type params_type
type(params_type), private :: params_inst
!
Expand Down Expand Up @@ -79,6 +81,9 @@ subroutine readParams( ncid )
! Max topographic slope for microtopography pdf sigma (unitless)
call readNcdioScalar(ncid, 'slopemax', subname, params_inst%slopemax)

call readNcdioScalar(ncid, 'zbedrock', subname, params_inst%zbedrock)
call readNcdioScalar(ncid, 'zbedrock_sf', subname, params_inst%zbedrock_sf)

end subroutine readParams

!------------------------------------------------------------------------
Expand Down Expand Up @@ -447,6 +452,12 @@ subroutine initVertical(bounds, glc_behavior, thick_wall, thick_roof)
call endrun( 'ERROR:: zbedrock not found on surface data set, and use_bedrock is true.'//errmsg(sourcefile, __LINE__) )
end if
end if
if (params_inst%zbedrock>=0._r8) then
zbedrock_in(:) = params_inst%zbedrock
end if
if (params_inst%zbedrock_sf/=1._r8) then
zbedrock_in(:) = params_inst%zbedrock_sf*zbedrock_in(:)
end if

! if use_bedrock = false, set zbedrock to lowest layer bottom interface
else
Expand Down
11 changes: 11 additions & 0 deletions src/main/pftconMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -162,6 +162,8 @@ module pftconMod
real(r8), allocatable :: taper (:) ! tapering ratio of height:radius_breast_height
real(r8), allocatable :: rstem_per_dbh (:) ! stem resistance per dbh (s/m/m)
real(r8), allocatable :: wood_density (:) ! wood density (kg/m3)
real(r8), allocatable :: crit_onset_gdd_sf(:)! scale factor for crit_onset_gdd
real(r8), allocatable :: ndays_on(:) ! number of days to complete leaf onset

! crop

Expand Down Expand Up @@ -502,6 +504,8 @@ subroutine InitAllocate (this)
allocate( this%taper (0:mxpft) )
allocate( this%rstem_per_dbh (0:mxpft) )
allocate( this%wood_density (0:mxpft) )
allocate( this%crit_onset_gdd_sf (0:mxpft) )
allocate( this%ndays_on (0:mxpft) )

end subroutine InitAllocate

Expand Down Expand Up @@ -843,6 +847,11 @@ subroutine InitRead(this)

call ncd_io('season_decid_temperate', this%season_decid_temperate, 'read', ncid, readvar=readv, posNOTonfile=.true.)
if ( .not. readv ) call endrun(msg=' ERROR: error in reading in pft data'//errMsg(sourcefile, __LINE__))
call ncd_io('crit_onset_gdd_sf', this%crit_onset_gdd_sf, 'read', ncid, readvar=readv, posNOTonfile=.true.)
if ( .not. readv ) call endrun(msg=' ERROR: error in reading in pft data'//errMsg(sourcefile, __LINE__))

call ncd_io('ndays_on', this%ndays_on, 'read', ncid, readvar=readv, posNOTonfile=.true.)
if ( .not. readv ) call endrun(msg=' ERROR: error in reading in pft data'//errMsg(sourcefile, __LINE__))

call ncd_io('pftpar20', this%pftpar20, 'read', ncid, readvar=readv, posNOTonfile=.true.)
if ( .not. readv ) call endrun(msg=' ERROR: error in reading in pft data'//errMsg(sourcefile, __LINE__))
Expand Down Expand Up @@ -1585,6 +1594,8 @@ subroutine Clean(this)
deallocate( this%rstem_per_dbh)
deallocate( this%wood_density)
deallocate( this%taper)
deallocate( this%crit_onset_gdd_sf)
deallocate( this%ndays_on)
end subroutine Clean

end module pftconMod
Expand Down

0 comments on commit 4333a66

Please sign in to comment.