TimeUtils.F90 Source File


Files dependent on this one

sourcefile~~timeutils.f90~~AfferentGraph sourcefile~timeutils.f90 TimeUtils.F90 sourcefile~mapl_capgridcomp.f90 MAPL_CapGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~timeutils.f90 sourcefile~mapl_historygridcomp.f90 MAPL_HistoryGridComp.F90 sourcefile~mapl_capgridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~mapl_historygridcomp.f90->sourcefile~timeutils.f90 sourcefile~test_timeutils.pf test_TimeUtils.pf sourcefile~test_timeutils.pf->sourcefile~timeutils.f90 sourcefile~comp_testing_driver.f90 Comp_Testing_Driver.F90 sourcefile~comp_testing_driver.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~extdatadrivergridcomp.f90 ExtDataDriverGridComp.F90 sourcefile~extdatadrivergridcomp.f90->sourcefile~mapl_historygridcomp.f90 sourcefile~mapl_cap.f90 MAPL_Cap.F90 sourcefile~mapl_cap.f90->sourcefile~mapl_capgridcomp.f90 sourcefile~extdatadriver.f90 ExtDataDriver.F90 sourcefile~extdatadriver.f90->sourcefile~extdatadrivergridcomp.f90 sourcefile~extdatadrivermod.f90 ExtDataDriverMod.F90 sourcefile~extdatadriver.f90->sourcefile~extdatadrivermod.f90 sourcefile~extdatadrivermod.f90->sourcefile~extdatadrivergridcomp.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 sourcefile~mapl.f90 MAPL.F90 sourcefile~mapl.f90->sourcefile~mapl_gridcomps.f90

Source Code

module MAPL_TimeUtilsMod

   implicit none
   private

   public :: is_valid_date
   public :: is_valid_time
   public :: is_valid_datetime

contains

   logical function is_valid_date(date) result(is_valid)

      ! Function to validate what MAPL expects for a valid date as
      ! passed to, say, History. 

      integer, intent(in) :: date

      integer :: year, month, day
      logical :: is_leap_year

      year  = date/10000
      month = mod(date,10000)/100
      day   = mod(date,100)

      is_leap_year = mod(year,4) == 0 .and. ( mod(year,100) /= 0  .or. mod(year,400) == 0 )

      is_valid = .true.

      ! Obvious cases
      if (date < 0) then
         is_valid = .false.
      else if (month == 0) then
         is_valid = .false.
      else if (month > 12) then
         is_valid = .false.
      else if (day == 0) then
         is_valid = .false.
      end if

      select case (month)
      ! 30 day months
      case (4,6,9,11)
         if (day > 30) is_valid = .false.
      ! February
      case (2)
         if (is_leap_year) then
            if (day > 29) is_valid = .false.
         else
            if (day > 28) is_valid = .false.
         end if
      ! 31 day months
      case default
         if (day > 31) is_valid = .false.
      end select

   end function is_valid_date

   logical function is_valid_time(time) result(is_valid)

      ! Function to validate what MAPL expects for a valid time as
      ! passed to, say, History. In this case it is a 6-digit integer
      ! that ranges from 000000 to 240000. 

      integer, intent(in) :: time

      integer :: hours, minutes, seconds

      hours   = time/10000
      minutes = mod(time,10000)/100
      seconds = mod(time,100)

      is_valid = .true.

      if (time < 0) then
         is_valid = .false.
      else if (time > 240000) then
         is_valid = .false.
      else if (hours > 24) then
         is_valid = .false.
      else if (minutes > 59) then
         is_valid = .false.
      else if (seconds > 59) then
         is_valid = .false.
      end if

   end function is_valid_time

   logical function is_valid_datetime(datetime) result(is_valid)

      ! Function to validate a datetime array

      integer, intent(in) :: datetime(2)

      is_valid = is_valid_date(datetime(1)) .and. is_valid_time(datetime(2))

   end function is_valid_datetime

end module MAPL_TimeUtilsMod