Skip to content

Commit

Permalink
Merge pull request #3404 from GEOS-ESM/feature/wdboggs/mapl3_freq_asp…
Browse files Browse the repository at this point in the history
…ect_ts_reftime_3358

Feature/wdboggs/mapl3 freq aspect ts reftime 3358
  • Loading branch information
tclune authored Feb 13, 2025
2 parents 1e26ca8 + ef99af4 commit 888f873
Show file tree
Hide file tree
Showing 3 changed files with 63 additions and 76 deletions.
24 changes: 12 additions & 12 deletions esmf_utils/ESMF_Time_Utilities.F90
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module mapl3g_ESMF_Time_Utilities
use esmf, I4 => ESMF_KIND_I4
use mapl_ErrorHandling
implicit none (type, external)
! private !wdb fixme deleteme should this be private
private

public :: zero_time_interval
public :: intervals_are_compatible
Expand All @@ -27,8 +27,8 @@ module mapl3g_ESMF_Time_Utilities
! smaller interval must divide the larger interval evenly
! assumes they have the same sign.
subroutine intervals_are_compatible(larger, smaller, compatible, rc)
type(ESMF_TimeInterval), intent(inout) :: larger
type(ESMF_TimeInterval), intent(inout) :: smaller
type(ESMF_TimeInterval), intent(in) :: larger
type(ESMF_TimeInterval), intent(in) :: smaller
logical, intent(out) :: compatible
integer, optional, intent(out) :: rc
integer :: status
Expand All @@ -49,10 +49,10 @@ end subroutine intervals_are_compatible
! intervals must be comparable, abs(interval1) >= abs(interval2)
! abs(interval2) must evenly divide absolute difference of times
subroutine times_and_intervals_are_compatible(interval1, time1, interval2, time2, compatible, rc)
type(ESMF_Time), intent(inout) :: time1
type(ESMF_Time), intent(inout) :: time2
type(ESMF_TimeInterval), intent(inout) :: interval1
type(ESMF_TimeInterval), intent(inout) :: interval2
type(ESMF_Time), intent(in) :: time1
type(ESMF_Time), intent(in) :: time2
type(ESMF_TimeInterval), intent(in) :: interval1
type(ESMF_TimeInterval), intent(in) :: interval2
logical, intent(out) :: compatible
integer, optional, intent(inout) :: rc
integer :: status
Expand All @@ -72,8 +72,8 @@ end subroutine times_and_intervals_are_compatible
! these combinations. Presumably ms, us, and ns for the smaller interval do
! not work.
subroutine can_compare_intervals(larger, smaller, comparable, rc)
type(ESMF_TimeInterval), intent(inout) :: larger
type(ESMF_TimeInterval), intent(inout) :: smaller
type(ESMF_TimeInterval), intent(in) :: larger
type(ESMF_TimeInterval), intent(in) :: smaller
logical, intent(out) :: comparable
integer, optional, intent(out) :: rc
integer :: status
Expand Down Expand Up @@ -101,7 +101,7 @@ function get_zero() result(zero)
end function get_zero

subroutine as_array(interval, units, rc)
type(ESMF_TimeInterval), intent(inout) :: interval
type(ESMF_TimeInterval), intent(in) :: interval
integer(kind=I4), intent(out) :: units(NUM_INTERVAL_UNITS)
integer, optional, intent(out) :: rc
integer :: status
Expand All @@ -113,7 +113,7 @@ subroutine as_array(interval, units, rc)
end subroutine as_array

logical function has_only_years_and_months(interval, rc)
type(ESMF_TimeInterval), intent(inout) :: interval
type(ESMF_TimeInterval), intent(in) :: interval
integer, optional, intent(out) :: rc
integer :: status
integer(kind=I4) :: units(NUM_INTERVAL_UNITS)
Expand All @@ -125,7 +125,7 @@ logical function has_only_years_and_months(interval, rc)
end function has_only_years_and_months

logical function has_no_years_or_months(interval, rc)
type(ESMF_TimeInterval), intent(inout) :: interval
type(ESMF_TimeInterval), intent(in) :: interval
integer, optional, intent(out) :: rc
integer :: status
integer(kind=I4) :: units(NUM_INTERVAL_UNITS)
Expand Down
99 changes: 41 additions & 58 deletions generic3g/specs/FrequencyAspect.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module mapl3g_FrequencyAspect
use mapl3g_AspectId
use mapl3g_StateItemAspect
use mapl3g_AccumulatorActionInterface
use mapl3g_ESMF_Time_Utilities, only: times_and_intervals_are_compatible, zero_time_interval
use esmf
implicit none
private
Expand All @@ -29,23 +30,15 @@ module mapl3g_FrequencyAspect
procedure :: set_timestep
procedure :: get_accumulation_type
procedure :: set_accumulation_type
procedure :: get_reference_time
procedure :: set_reference_time
procedure, private :: zero_timestep
end type FrequencyAspect

interface FrequencyAspect
module procedure :: new_FrequencyAspect
end interface FrequencyAspect

interface operator(.divides.)
module procedure :: aspect_divides
end interface operator(.divides.)

! This value should not be accessed directly. Use get_zero() instead.
! There is no constructor for ESMF_TimeInterval, so the value cannot be initialized
! at construction. The get_zero() function initializes the value the first time
! and returns a pointer to the value.
type(ESMF_TimeInterval), target :: ZERO_TI

contains

function new_FrequencyAspect(timeStep, refTime, accumulation_type) result(aspect)
Expand All @@ -58,9 +51,9 @@ function new_FrequencyAspect(timeStep, refTime, accumulation_type) result(aspect
call aspect%set_time_dependent(.FALSE.)
call aspect%set_accumulation_type(INSTANTANEOUS)
call aspect%zero_timestep()
if(present(timestep)) aspect%timestep_ = timestep
if(present(timeStep)) aspect%timestep_ = timeStep
if(present(refTime)) aspect%refTime_ = refTime
if(present(accumulation_type)) aspect%accumulation_type_ = accumulation_type
if(present(accumulation_type)) call aspect%set_accumulation_type(accumulation_type)

end function new_FrequencyAspect

Expand All @@ -72,14 +65,30 @@ function get_timestep(this) result(ts)

end function get_timestep

subroutine set_timestep(this, timestep)
subroutine set_timestep(this, timeStep)
class(FrequencyAspect), intent(inout) :: this
type(ESMF_TimeInterval), intent(in) :: timestep
type(ESMF_TimeInterval), intent(in) :: timeStep

this%timestep_ = timestep
this%timestep_ = timeStep

end subroutine set_timestep

function get_reference_time(this) result(time)
type(ESMF_Time) :: time
class(FrequencyAspect), intent(in) :: this

time = this%refTime_

end function get_reference_time

subroutine set_reference_time(this, time)
class(FrequencyAspect), intent(inout) :: this
type(ESMF_Time), intent(in) :: time

this%refTime_ = time

end subroutine set_reference_time

subroutine zero_timestep(this)
class(FrequencyAspect), intent(inout) :: this

Expand Down Expand Up @@ -109,19 +118,19 @@ end subroutine set_accumulation_type
logical function matches(src, dst) result(does_match)
class(FrequencyAspect), intent(in) :: src
class(StateItemAspect), intent(in) :: dst
type(ESMF_TimeInterval) :: src_timestep, dst_timestep
type(ESMF_TimeInterval) :: this_timestep, other_timestep
type(ESMF_TimeInterval), pointer :: zero

does_match = .TRUE.
zero => get_zero()
src_timestep = src%get_timestep()
if(src_timestep == zero) return
zero => zero_time_interval()
this_timestep = src%get_timestep()
if(this_timestep == zero) return
select type(dst)
class is (FrequencyAspect)
dst_timestep = dst%get_timestep()
if(dst_timestep == zero) return
other_timestep = dst%get_timestep()
if(other_timestep == zero) return
if(.not. accumulation_type_is_valid(dst%get_accumulation_type())) return
does_match = dst_timestep == src_timestep
does_match = other_timestep == this_timestep
end select

end function matches
Expand All @@ -132,19 +141,21 @@ function make_action(src, dst, other_aspects, rc) result(action)
class(StateItemAspect), intent(in) :: dst
type(AspectMap), target, intent(in) :: other_aspects
integer, optional, intent(out) :: rc

integer :: status
character(len=:), allocatable :: accumulation_type

select type(dst)
class is (FrequencyAspect)
call get_accumulator_action(dst%get_accumulation_type(), ESMF_TYPEKIND_R4, action, _RC)
accumulation_type = dst%get_accumulation_type()
call get_accumulator_action(accumulation_type, ESMF_TYPEKIND_R4, action, _RC)
_ASSERT(allocated(action), 'Unable to allocate action')
class default
allocate(action,source=NullAction())
_FAIL('FrequencyAspect cannot convert from other class.')
end select

_RETURN(_SUCCESS)
_UNUSED_DUMMY(src)
end function make_action

subroutine connect_to_export(this, export, actual_pt, rc)
Expand All @@ -170,50 +181,22 @@ end function supports_conversion_general
logical function supports_conversion_specific(src, dst) result(supports)
class(FrequencyAspect), intent(in) :: src
class(StateItemAspect), intent(in) :: dst
integer :: status

select type(dst)
class is (FrequencyAspect)
supports = src .divides. dst
call times_and_intervals_are_compatible(&
& src%get_timestep(), src%get_reference_time(),&
& dst%get_timestep(), dst%get_reference_time(),&
& supports, rc=status)
supports = supports .and. status == _SUCCESS
end select

end function supports_conversion_specific

logical function aspect_divides(factor, base)
class(FrequencyAspect), intent(in) :: factor
class(FrequencyAspect), intent(in) :: base

aspect_divides = interval_divides(factor%get_timestep(), base%get_timestep())

end function aspect_divides

logical function interval_divides(factor, base) result(lval)
type(ESMF_TimeInterval), intent(in) :: factor
type(ESMF_TimeInterval), intent(in) :: base
type(ESMF_TimeInterval), pointer :: zero

lval = .FALSE.
zero => get_zero()
if(factor == zero) return
lval = mod(base, factor) == zero

end function interval_divides

function get_zero() result(zero)
type(ESMF_TimeInterval), pointer :: zero
logical, save :: zero_is_uninitialized = .TRUE.

if(zero_is_uninitialized) then
call ESMF_TimeIntervalSet(ZERO_TI, ns=0)
zero_is_uninitialized = .FALSE.
end if
zero => ZERO_TI

end function get_zero

function get_aspect_id() result(aspect_id)
type(AspectId) :: aspect_id
aspect_id = FREQUENCY_ASPECT_ID
end function get_aspect_id


end module mapl3g_FrequencyAspect
16 changes: 10 additions & 6 deletions generic3g/tests/Test_Aspects.pf
Original file line number Diff line number Diff line change
Expand Up @@ -285,13 +285,15 @@ contains
type(FrequencyAspect) :: import, export

type(ESMF_TimeInterval) :: dt1, dt2
type(ESMF_Time) :: time1, time2

call ESMF_TimeIntervalSet(dt1, s=4)
call ESMF_TimeIntervalSet(dt2, s=2) ! commensurate
call ESMF_TimeSet(time1, s=0)
call ESMF_TimeSet(time2, s=0)

import = FrequencyAspect(dt1, accumulation_type='mean')
export = FrequencyAspect(dt2)

import = FrequencyAspect(dt2, time2, accumulation_type='mean')
export = FrequencyAspect(dt1, time1)
@assert_that(export%can_connect_to(import), is(true()))

end subroutine test_can_connect_accum_mean
Expand All @@ -302,13 +304,15 @@ contains
type(FrequencyAspect) :: import, export

type(ESMF_TimeInterval) :: dt1, dt2
type(ESMF_Time) :: time1, time2

call ESMF_TimeIntervalSet(dt1, s=4)
call ESMF_TimeIntervalSet(dt2, s=3) ! not commensurate
call ESMF_TimeSet(time1, s=0)
call ESMF_TimeSet(time2, s=0)

import = FrequencyAspect(dt1, accumulation_type='mean')
export = FrequencyAspect(dt2)

import = FrequencyAspect(dt2, time2, accumulation_type='mean')
export = FrequencyAspect(dt1, time1)
@assert_that(export%can_connect_to(import), is(false()))

end subroutine test_can_connect_accum_fail
Expand Down

0 comments on commit 888f873

Please sign in to comment.