MAPL_DateTime_Parsing_ESMF.F90 Source File


This file depends on

sourcefile~~mapl_datetime_parsing_esmf.f90~~EfferentGraph sourcefile~mapl_datetime_parsing_esmf.f90 MAPL_DateTime_Parsing_ESMF.F90 sourcefile~keywordenforcer.f90 KeywordEnforcer.F90 sourcefile~mapl_datetime_parsing_esmf.f90->sourcefile~keywordenforcer.f90 sourcefile~mapl_exceptionhandling.f90 MAPL_ExceptionHandling.F90 sourcefile~mapl_datetime_parsing_esmf.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_datetime_parsing_esmf.f90~~AfferentGraph sourcefile~mapl_datetime_parsing_esmf.f90 MAPL_DateTime_Parsing_ESMF.F90 sourcefile~mapl_netcdf.f90 MAPL_NetCDF.F90 sourcefile~mapl_netcdf.f90->sourcefile~mapl_datetime_parsing_esmf.f90 sourcefile~test_mapl_datetime_parsing_esmf.pf test_MAPL_DateTime_Parsing_ESMF.pf sourcefile~test_mapl_datetime_parsing_esmf.pf->sourcefile~mapl_datetime_parsing_esmf.f90 sourcefile~mapl_geosatmaskmod.f90 MAPL_GeosatMaskMod.F90 sourcefile~mapl_geosatmaskmod.f90->sourcefile~mapl_netcdf.f90 sourcefile~mapl_obsutil.f90 MAPL_ObsUtil.F90 sourcefile~mapl_geosatmaskmod.f90->sourcefile~mapl_obsutil.f90 sourcefile~mapl_geosatmaskmod_smod.f90 MAPL_GeosatMaskMod_smod.F90 sourcefile~mapl_geosatmaskmod_smod.f90->sourcefile~mapl_netcdf.f90 sourcefile~mapl_geosatmaskmod_smod.f90->sourcefile~mapl_geosatmaskmod.f90 sourcefile~mapl_obsutil.f90->sourcefile~mapl_netcdf.f90 sourcefile~mapl_trajectorymod_smod.f90 MAPL_TrajectoryMod_smod.F90 sourcefile~mapl_trajectorymod_smod.f90->sourcefile~mapl_netcdf.f90 sourcefile~mapl_trajectorymod_smod.f90->sourcefile~mapl_obsutil.f90 sourcefile~mapl_trajectorymod.f90 MAPL_TrajectoryMod.F90 sourcefile~mapl_trajectorymod_smod.f90->sourcefile~mapl_trajectorymod.f90 sourcefile~test_mapl_netcdf.pf test_MAPL_NetCDF.pf sourcefile~test_mapl_netcdf.pf->sourcefile~mapl_netcdf.f90 sourcefile~mapl_historycollection.f90 MAPL_HistoryCollection.F90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_geosatmaskmod.f90 sourcefile~mapl_historycollection.f90->sourcefile~mapl_trajectorymod.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_geosatmaskmod.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_obsutil.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_historycollection.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~mapl_trajectorymod.f90 sourcefile~mapl_swathgridfactory.f90 MAPL_SwathGridFactory.F90 sourcefile~mapl_swathgridfactory.f90->sourcefile~mapl_obsutil.f90 sourcefile~mapl_trajectorymod.f90->sourcefile~mapl_obsutil.f90 sourcefile~mapl_xygridfactory.f90 MAPL_XYGridFactory.F90 sourcefile~mapl_xygridfactory.f90->sourcefile~mapl_obsutil.f90 sourcefile~extdatadrivergridcomp.f90 ExtDataDriverGridComp.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~mapl_gridmanager.f90 MAPL_GridManager.F90 sourcefile~mapl_gridmanager.f90->sourcefile~mapl_swathgridfactory.f90 sourcefile~mapl_gridmanager.f90->sourcefile~mapl_xygridfactory.f90

Source Code

#include "MAPL_Exceptions.h"
#include "MAPL_ErrLog.h"
module MAPL_DateTime_Parsing_ESMF
   use MAPL_KeywordEnforcerMod
   use MAPL_ExceptionHandling
   use MAPL_DateTime_Parsing
   use ESMF

   implicit none

   public :: set_ESMF_TimeInterval, set_ESMF_Time_from_ISO8601

   interface set_ESMF_TimeInterval
      module procedure :: set_ESMF_TimeInterval_from_datetime_duration
   end interface set_ESMF_TimeInterval

contains

   subroutine set_ESMF_TimeInterval_from_datetime_duration(interval, duration, rc)
      type(ESMF_TimeInterval), intent(inout) :: interval
      class(datetime_duration), intent(in) :: duration
      integer, optional, intent(out) :: rc
      integer :: status

      ! Get duration(s) from datetime_duration

      ! Set ESMF_TimeInterval

      if(duration % year_is_set()) then
         call ESMF_TimeIntervalSet(interval, yy = duration % year, _RC)
      end if

      if(duration % month_is_set()) then
         call ESMF_TimeIntervalSet(interval, yy = duration % month, _RC)
      end if

      if(duration % day_is_set()) then
         call ESMF_TimeIntervalSet(interval, yy = duration % day, _RC)
      end if

      if(duration % hour_is_real()) then
         call ESMF_TimeIntervalSet(interval, h_r8 = duration % hour_real, _RC)
      else if(duration % hour_is_set()) then
         call ESMF_TimeIntervalSet(interval, h = duration % hour, _RC)
      end if
         
      if(duration % minute_is_real()) then
         call ESMF_TimeIntervalSet(interval, m_r8 = duration % minute_real, _RC)
      else if(duration % minute_is_set()) then
         call ESMF_TimeIntervalSet(interval, m = duration % minute, _RC)
      end if

      if(duration % second_is_real()) then
         call ESMF_TimeIntervalSet(interval, s_r8 = duration % second_real, _RC)
      else if(duration % second_is_set()) then
         call ESMF_TimeIntervalSet(interval, s = duration % second, _RC)
      end if

      _RETURN(_SUCCESS)

   end subroutine set_ESMF_TimeInterval_from_datetime_duration

   subroutine set_ESMF_Time_from_ISO8601(time, isostring, rc)
       type(ESMF_Time), intent(inout) :: time
       character(len=*), intent(in) :: isostring
       integer, optional, intent(out) :: rc
       integer :: status

       call ESMF_TimeSet(time, isostring, _RC)

       _RETURN(_SUCCESS)

   end subroutine set_ESMF_Time_from_ISO8601
   
end module MAPL_DateTime_Parsing_ESMF