Skip to content

Commit

Permalink
Merge pull request #2 from billsacks/agsys
Browse files Browse the repository at this point in the history
Add agsys_phases_type and accumulated_thermal_time_phases
  • Loading branch information
pengbinpeluo authored Nov 1, 2019
2 parents 0a88295 + 10c198f commit eb2fb5b
Show file tree
Hide file tree
Showing 4 changed files with 92 additions and 9 deletions.
9 changes: 6 additions & 3 deletions src/agsys/ctsm_interface/AgSys.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,8 @@ module AgSys
use decompMod, only : bounds_type
use AgSysGeneral, only : agsys_general_type
use AgSysParams, only : agsys_params_type
use AgSysParamReader, only : ReadParams
use AgSysPhases, only : agsys_phases_type
use AgSysParamReader, only : ReadParams, ReadPhases
use AgSysClimate, only : agsys_climate_type
use AgSysPhenology, only : agsys_phenology_type
!
Expand All @@ -23,8 +24,9 @@ module AgSys

type, public :: agsys_type
private
type(agsys_general_type) :: agsys_general_inst
type(agsys_general_type) :: agsys_general_inst
type(agsys_params_type) :: agsys_params_inst
type(agsys_phases_type) :: agsys_phases_inst
type(agsys_climate_type) :: agsys_climate_inst
type(agsys_phenology_type) :: agsys_phenology_inst

Expand Down Expand Up @@ -89,7 +91,8 @@ subroutine Init(this, bounds)

call this%agsys_general_inst%Init(bounds)
call ReadParams(this%agsys_params_inst)
call this%agsys_climate_inst%Init(bounds)
call ReadPhases(this%agsys_phases_inst)
call this%agsys_climate_inst%Init(bounds, this%agsys_phases_inst)
call this%agsys_phenology_inst%Init(bounds)

end subroutine Init
Expand Down
26 changes: 20 additions & 6 deletions src/agsys/ctsm_interface/AgSysClimate.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ module AgSysClimate
use shr_kind_mod , only : r8 => shr_kind_r8
use shr_infnan_mod , only : nan => shr_infnan_nan, assignment(=)
use decompMod , only : bounds_type
use AgSysPhases , only : agsys_phases_type
!
implicit none
private
Expand All @@ -19,8 +20,16 @@ module AgSysClimate
private

! Public data members
real(r8), pointer, public :: accumulated_thermal_time_patch(:) ! accumulated thermal time (deg-days)
real(r8), pointer, public :: accumulated_emerged_thermal_time_patch(:) ! accumulated thermal time since emergence (deg-days)
real(r8), pointer, public :: accumulated_thermal_time_patch(:) ! accumulated thermal time (deg-days)

! TODO(wjs, 2019-11-01) We may not need all of these - i.e., it maybe unnecessary to
! have both an emerged_thermal_time and thermal time for each phase (since the former
! can be calculated from the latter if needed). Also, we may not actually need the
! full generality of having thermal time for each phase: it may be sufficient, for
! example, to store the thermal time just for the previous phase. (If we can avoid
! supporting this full generality, that could be good to avoid restart file bloat.)
real(r8), pointer, public :: accumulated_emerged_thermal_time_patch(:) ! accumulated thermal time since emergence (deg-days)
real(r8), pointer, public :: accumulated_thermal_time_phases_patch(:,:) ! accumulated thermal time for each phase (deg-days) [phase, patch]
contains
procedure, public :: AgSysClimateTimeStep

Expand Down Expand Up @@ -61,32 +70,34 @@ end subroutine AgSysClimateTimeStep
! ========================================================================

!-----------------------------------------------------------------------
subroutine Init(this, bounds)
subroutine Init(this, bounds, agsys_phases_inst)
!
! !DESCRIPTION:
! Initialize this agsys_climate_type insntance
! Initialize this agsys_climate_type instance
!
! !ARGUMENTS:
class(agsys_climate_type), intent(inout) :: this
type(bounds_type), intent(in) :: bounds
type(agsys_phases_type), intent(in) :: agsys_phases_inst
!
! !LOCAL VARIABLES:

character(len=*), parameter :: subname = 'Init'
!-----------------------------------------------------------------------

call this%InitAllocate(bounds)
call this%InitAllocate(bounds, agsys_phases_inst)
end subroutine Init

!-----------------------------------------------------------------------
subroutine InitAllocate(this, bounds)
subroutine InitAllocate(this, bounds, agsys_phases_inst)
!
! !DESCRIPTION:
! Allocate components of this agsys_climate_type instance
!
! !ARGUMENTS:
class(agsys_climate_type), intent(inout) :: this
type(bounds_type), intent(in) :: bounds
type(agsys_phases_type), intent(in) :: agsys_phases_inst
!
! !LOCAL VARIABLES:

Expand All @@ -101,6 +112,9 @@ subroutine InitAllocate(this, bounds)
allocate(this%accumulated_thermal_time_patch(begp:endp)) ; this%accumulated_thermal_time_patch(:) = nan
allocate(this%accumulated_emerged_thermal_time_patch(begp:endp)) ; this%accumulated_emerged_thermal_time_patch(:) = nan

allocate(this%accumulated_thermal_time_phases_patch(1:agsys_phases_inst%max_phases, begp:endp))
this%accumulated_thermal_time_phases_patch(:,:) = nan

end associate

end subroutine InitAllocate
Expand Down
18 changes: 18 additions & 0 deletions src/agsys/ctsm_interface/AgSysParamReader.F90
Original file line number Diff line number Diff line change
Expand Up @@ -9,12 +9,14 @@ module AgSysParamReader
use shr_kind_mod , only : r8 => shr_kind_r8
use shr_infnan_mod , only : nan => shr_infnan_nan, assignment(=)
use AgSysParams , only : agsys_params_type
use AgSysPhases , only : agsys_phases_type
!
implicit none
private

! !PUBLIC ROUTINES:
public :: ReadParams
public :: ReadPhases

character(len=*), parameter, private :: sourcefile = &
__FILE__
Expand All @@ -37,4 +39,20 @@ subroutine ReadParams(params)

end subroutine ReadParams

!-----------------------------------------------------------------------
subroutine ReadPhases(phases)
!
! !DESCRIPTION:
! Read phase descriptions for each crop
!
! !ARGUMENTS:
type(agsys_phases_type), intent(inout) :: phases
!
! !LOCAL VARIABLES:

character(len=*), parameter :: subname = 'ReadPhases'
!-----------------------------------------------------------------------

end subroutine ReadPhases

end module AgSysParamReader
48 changes: 48 additions & 0 deletions src/agsys/science/AgSysPhases.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,48 @@
module AgSysPhases

!-----------------------------------------------------------------------
! !DESCRIPTION:
! Derived type describing the translation between a stage index and the phase / stage
! names or phase type.
!
! !USES:

!
implicit none
private

! !PUBLIC DATA:

integer, parameter, public :: phase_type_unused = -1
integer, parameter, public :: phase_type_generic = 0
integer, parameter, public :: phase_type_germinating = 1
integer, parameter, public :: phase_type_emerging = 2
integer, parameter, public :: phase_type_node_number = 3
integer, parameter, public :: phase_type_leaf_appearance = 4
integer, parameter, public :: phase_type_end = 5
integer, parameter, public :: phase_type_maxval = 5

integer, parameter, public :: max_phase_name_len = 64 ! maximum number of characters in names of phases / stages

! !PUBLIC TYPES:
type, public :: agsys_phases_type
private

! Public data members
integer, public :: max_phases ! maximum number of phases used by any crop (arrays are dimensioned to be this large)
integer, allocatable, public :: num_phases_for_crop(:) ! [crop_type] number of phases used by each crop

! Each of these arrays are dimensioned [stage, crop_type]. Stage is defined as a
! point in time (e.g., the time of sowing, or the time of germination). Phase is
! defined as the span of time between two stages (e.g., germinating is the phase
! between sowing and germination). 'phase' variables give the phase whose start point
! is the given stage. For example, if crop type 7 has the first two stages 'sowing'
! and 'germination', then phase_name(1,7) = 'germinating'. Conversely, if
! phase_name(3,7) = 'juvenile', then the name of the stage that triggers the start
! of the juvenile phase is given by stage_name(3,7) (e.g., 'emergence').
character(len=max_phase_name_len), allocatable, public :: stage_name(:,:) ! [stage, crop_type]; name of the given stage
character(len=max_phase_name_len), allocatable, public :: phase_name(:,:) ! [stage, crop_type]; name of the phase whose start point is the given stage
integer , allocatable, public :: phase_type(:,:) ! [stage, crop_type]; each value is one of the above phase_type_* constants
end type agsys_phases_type

end module AgSysPhases

0 comments on commit eb2fb5b

Please sign in to comment.