MAPL_SimpleAlarm.F90 Source File


This file depends on

sourcefile~~mapl_simplealarm.f90~~EfferentGraph sourcefile~mapl_simplealarm.f90 MAPL_SimpleAlarm.F90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~mapl_simplealarm.f90->sourcefile~mapl_exceptionhandling.f90 sourcefile~errorhandling.f90 ErrorHandling.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~errorhandling.f90 sourcefile~mapl_throw.f90 MAPL_Throw.F90 sourcefile~mapl_exceptionhandling.f90->sourcefile~mapl_throw.f90 sourcefile~errorhandling.f90->sourcefile~mapl_throw.f90

Files dependent on this one

sourcefile~~mapl_simplealarm.f90~~AfferentGraph sourcefile~mapl_simplealarm.f90 MAPL_SimpleAlarm.F90 sourcefile~extdatagridcompmod.f90 ExtDataGridCompMod.F90 sourcefile~extdatagridcompmod.f90->sourcefile~mapl_simplealarm.f90 sourcefile~fieldbundleread.f90 FieldBundleRead.F90 sourcefile~fieldbundleread.f90->sourcefile~mapl_simplealarm.f90 sourcefile~extdatadrivergridcomp.f90 ExtDataDriverGridComp.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~extdatagridcompmod.f90 sourcefile~mapl.f90 MAPL.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~mapl.f90 sourcefile~mapl.f90->sourcefile~fieldbundleread.f90 sourcefile~mapl_bundleio_test.f90 mapl_bundleio_test.F90 sourcefile~mapl_bundleio_test.f90->sourcefile~fieldbundleread.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~extdatagridcompmod.f90 sourcefile~regrid_util.f90 Regrid_Util.F90 sourcefile~regrid_util.f90->sourcefile~fieldbundleread.f90 sourcefile~regrid_util.f90->sourcefile~mapl.f90 sourcefile~ut_extdata.f90 ut_ExtData.F90 sourcefile~ut_extdata.f90->sourcefile~extdatagridcompmod.f90 sourcefile~capdriver.f90 CapDriver.F90 sourcefile~capdriver.f90->sourcefile~mapl.f90 sourcefile~extdataroot_gridcomp.f90 ExtDataRoot_GridComp.F90 sourcefile~capdriver.f90->sourcefile~extdataroot_gridcomp.f90 sourcefile~comp_testing_driver.f90 Comp_Testing_Driver.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl.f90 sourcefile~comp_testing_driver.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~extdatadriver.f90 ExtDataDriver.F90 sourcefile~extdatadriver.f90->sourcefile~extdatadrivergridcomp.f90 sourcefile~extdatadriver.f90->sourcefile~mapl.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadriver.f90->sourcefile~extdatadrivermod.f90 sourcefile~extdatadriver.f90->sourcefile~extdataroot_gridcomp.f90 sourcefile~extdatadrivermod.f90->sourcefile~extdatadrivergridcomp.f90 sourcefile~extdatadrivermod.f90->sourcefile~mapl.f90 sourcefile~extdatadrivermod.f90->sourcefile~extdataroot_gridcomp.f90 sourcefile~extdataroot_gridcomp.f90->sourcefile~mapl.f90 sourcefile~varspecdescription.f90 VarspecDescription.F90 sourcefile~extdataroot_gridcomp.f90->sourcefile~varspecdescription.f90 sourcefile~mapl_cap.f90 MAPL_Cap.F90 sourcefile~mapl_cap.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~mapl_demo_fargparse.f90 MAPL_demo_fargparse.F90 sourcefile~mapl_demo_fargparse.f90->sourcefile~mapl.f90 sourcefile~pfio_mapl_demo.f90 pfio_MAPL_demo.F90 sourcefile~pfio_mapl_demo.f90->sourcefile~mapl.f90 sourcefile~time_ave_util.f90 time_ave_util.F90 sourcefile~time_ave_util.f90->sourcefile~mapl.f90 sourcefile~varspecdescription.f90->sourcefile~mapl.f90 sourcefile~mapl_gridcomps.f90 MAPL_GridComps.F90 sourcefile~mapl_gridcomps.f90->sourcefile~mapl_cap.f90 sourcefile~mapl_nuopcwrappermod.f90 MAPL_NUOPCWrapperMod.F90 sourcefile~mapl_nuopcwrappermod.f90->sourcefile~mapl_cap.f90

Source Code

#include "MAPL_ErrLog.h"
#include "unused_dummy.H"

module MAPL_SimpleAlarm
   use ESMF
   use MAPL_ExceptionHandling

   implicit none
   private

   public SimpleAlarm

   type :: SimpleAlarm
      private
      type(ESMF_Time) :: reference_time
      type(ESMF_TimeInterval) :: ring_interval
      contains
         procedure :: is_ringing
   end type SimpleAlarm

   interface SimpleAlarm
      module procedure new_simple_alarm
   end interface SimpleAlarm

contains

   function new_simple_alarm(reference_time,ring_interval,rc) result(new_alarm)
      type(ESMF_Time), intent(in) :: reference_time
      type(ESMF_TimeInterval), intent(in) :: ring_interval
      integer, optional, intent(out) :: rc

      type(SimpleAlarm) :: new_alarm

      new_alarm%reference_time = reference_time
      new_alarm%ring_interval = ring_interval
 
      _RETURN(_SUCCESS)
   end function new_simple_alarm

   function is_ringing(this,current_time,rc) result(ringing)
      class(SimpleAlarm), intent(inout) :: this
      type(ESMF_Time), intent(inout) :: current_time
      integer, optional, intent(out) :: rc

      integer :: status
      logical :: ringing
      integer(ESMF_KIND_I8) :: ring_interval_i8, elapsed_interval_i8
      type(ESMF_TimeInterval) :: elapsed_interval

      elapsed_interval = current_time - this%reference_time
      call ESMF_TimeIntervalGet(elapsed_interval,s_i8=elapsed_interval_i8,rc=status)
      _VERIFY(status)
      call ESMF_TimeIntervalGet(this%ring_interval,s_i8=ring_interval_i8,rc=status)
      _VERIFY(status)
      if (mod(elapsed_interval_i8,ring_interval_i8) == 0) then
         ringing=.true.
      else
         ringing=.false.
      end if
      _RETURN(_SUCCESS)
   end function is_ringing

end module MAPL_SimpleAlarm