get_time_info Subroutine

public subroutine get_time_info(this, startTime, startYear, startMonth, startDay, startHour, startMin, startSec, units, timeVector, rc)

Type Bound

FileMetadataUtils

Arguments

Type IntentOptional Attributes Name
class(FileMetadataUtils), intent(inout) :: this
type(ESMF_Time), intent(inout), optional :: startTime
integer, intent(out), optional :: startYear
integer, intent(out), optional :: startMonth
integer, intent(out), optional :: startDay
integer, intent(out), optional :: startHour
integer, intent(out), optional :: startMin
integer, intent(out), optional :: startSec
character(len=*), intent(out), optional :: units
type(ESMF_Time), optional, allocatable :: timeVector(:)
integer, intent(out), optional :: rc

Calls

proc~~get_time_info~~CallsGraph proc~get_time_info FileMetadataUtils%get_time_info ESMF_TimeGet ESMF_TimeGet proc~get_time_info->ESMF_TimeGet ESMF_TimeIntervalSet ESMF_TimeIntervalSet proc~get_time_info->ESMF_TimeIntervalSet ESMF_TimeSet ESMF_TimeSet proc~get_time_info->ESMF_TimeSet interface~mapl_assert MAPL_Assert proc~get_time_info->interface~mapl_assert none~get_attribute Variable%get_attribute proc~get_time_info->none~get_attribute none~get_coordinate_data CoordinateVariable%get_coordinate_data proc~get_time_info->none~get_coordinate_data none~get_coordinate_variable FileMetadata%get_coordinate_variable proc~get_time_info->none~get_coordinate_variable none~get_value UnlimitedEntity%get_value proc~get_time_info->none~get_value proc~get_coordinate_info FileMetadataUtils%get_coordinate_info proc~get_time_info->proc~get_coordinate_info proc~get_file_name FileMetadataUtils%get_file_name proc~get_time_info->proc~get_file_name proc~mapl_return MAPL_Return proc~get_time_info->proc~mapl_return proc~mapl_verify MAPL_Verify proc~get_time_info->proc~mapl_verify none~get_attribute->interface~mapl_assert none~get_attribute->proc~mapl_return none~at~140 StringAttributeMap%at none~get_attribute->none~at~140 none~get_coordinate_data->proc~mapl_return none~get_coordinate_variable->interface~mapl_assert none~get_coordinate_variable->proc~mapl_return none~at~5 StringVariableMap%at none~get_coordinate_variable->none~at~5 none~get_value->proc~mapl_return proc~get_coordinate_info->interface~mapl_assert proc~get_coordinate_info->none~get_attribute proc~get_coordinate_info->none~get_coordinate_data proc~get_coordinate_info->none~get_coordinate_variable proc~get_coordinate_info->none~get_value proc~get_coordinate_info->proc~get_file_name proc~get_coordinate_info->proc~mapl_return proc~get_coordinate_info->proc~mapl_verify none~get_dimension FileMetadata%get_dimension proc~get_coordinate_info->none~get_dimension none~get_ith_dimension Variable%get_ith_dimension proc~get_coordinate_info->none~get_ith_dimension proc~var_has_attr FileMetadataUtils%var_has_attr proc~get_coordinate_info->proc~var_has_attr proc~get_file_name->proc~mapl_return at at proc~mapl_return->at insert insert proc~mapl_return->insert proc~mapl_throw_exception MAPL_throw_exception proc~mapl_return->proc~mapl_throw_exception proc~mapl_verify->proc~mapl_throw_exception none~find~39 StringAttributeMap%find none~at~140->none~find~39 none~find~2 StringVariableMap%find none~at~5->none~find~2 none~get_dimension->proc~mapl_return none~get_dimension->at find find none~get_dimension->find none~get_ith_dimension->proc~mapl_return none~get_ith_dimension->at proc~var_has_attr->interface~mapl_assert proc~var_has_attr->proc~get_file_name proc~var_has_attr->proc~mapl_return proc~var_has_attr->proc~mapl_verify none~get_variable FileMetadata%get_variable proc~var_has_attr->none~get_variable none~is_attribute_present Variable%is_attribute_present proc~var_has_attr->none~is_attribute_present none~get_variable->proc~mapl_return none~get_variable->none~at~5 none~is_attribute_present->proc~mapl_return none~is_attribute_present->none~at~140

Called by

proc~~get_time_info~~CalledByGraph proc~get_time_info FileMetadataUtils%get_time_info none~detect_metadata ExtDataFileStream%detect_metadata none~detect_metadata->proc~get_time_info proc~get_file_times get_file_times proc~get_file_times->proc~get_time_info proc~get_file_times~2 get_file_times proc~get_file_times~2->proc~get_time_info proc~mapl_read_bundle MAPL_read_bundle proc~mapl_read_bundle->proc~get_time_info proc~run_component_driver run_component_driver proc~run_component_driver->proc~get_time_info proc~fillin_primary ExtDataOldTypesCreator%fillin_primary proc~fillin_primary->none~detect_metadata proc~main main proc~main->proc~get_file_times proc~main->proc~mapl_read_bundle proc~main~2 main proc~main~2->proc~run_component_driver program~time_ave time_ave program~time_ave->proc~get_file_times~2 program~time_ave->proc~mapl_read_bundle program~ut_regridding ut_ReGridding program~ut_regridding->proc~mapl_read_bundle program~comp_testing_driver comp_testing_driver program~comp_testing_driver->proc~main~2 program~regrid_util Regrid_Util program~regrid_util->proc~main

Source Code

   subroutine get_time_info(this,startTime,startyear,startmonth,startday,starthour,startmin,startsec,units,timeVector,rc)
      class (FileMetadataUtils), intent(inout) :: this
      type(ESMF_Time), optional, intent(inout) :: startTime
      integer,optional,intent(out) ::        startYear 
      integer,optional,intent(out) ::        startMonth
      integer,optional,intent(out) ::        startDay 
      integer,optional,intent(out) ::        startHour
      integer,optional,intent(out) ::        startMin 
      integer,optional,intent(out) ::        startSec
      type(ESMF_Time), allocatable, optional :: timeVector(:)
      type(ESMF_Time), allocatable :: tVec(:)
      character(len=*), optional, intent(out) :: units
      integer, optional, intent(out) :: rc

      integer :: status
      character(:), allocatable :: fname
      class(CoordinateVariable), pointer :: var
      type(Attribute), pointer :: attr
      class(*), pointer :: pTimeUnits
      character(len=ESMF_MAXSTR) :: timeUnits,tUnits
      integer :: i,tsize

      integer ypos(2), mpos(2), dpos(2), hpos(2), spos(2)
      integer strlen
      integer firstdash, lastdash
      integer firstcolon, lastcolon
      integer lastspace,since_pos
      integer year,month,day,hour,min,sec
      type(ESMF_Time) :: unmodStartTime
      class(*), pointer :: ptr(:)
      real(REAL64), allocatable :: tr_r64(:)
      type(ESMF_TimeInterval) :: tint

      fname = this%get_file_name(_RC)
      var => this%get_coordinate_variable('time',rc=status)
      _VERIFY(status)
      attr => var%get_attribute('units')
      ptimeUnits => attr%get_value()
      select type(pTimeUnits)
      type is (character(*))
         timeUnits = pTimeUnits
         strlen = LEN_TRIM (TimeUnits)

         since_pos = index(TimeUnits, 'since')
         tUnits = trim(TimeUnits(:since_pos-1))
         if (present(units)) units = trim(tUnits)

         firstdash = index(TimeUnits, '-')
         lastdash  = index(TimeUnits, '-', BACK=.TRUE.)

         if (firstdash .LE. 0 .OR. lastdash .LE. 0) then
           rc = -1
           return
         endif

         ypos(2) = firstdash - 1
         mpos(1) = firstdash + 1
         ypos(1) = ypos(2) - 3

         mpos(2) = lastdash - 1
         dpos(1) = lastdash + 1
         dpos(2) = dpos(1) + 1

         read ( TimeUnits(ypos(1):ypos(2)), * ) year
         read ( TimeUnits(mpos(1):mpos(2)), * ) month
         read ( TimeUnits(dpos(1):dpos(2)), * ) day

         firstcolon = index(TimeUnits, ':')
         if (firstcolon .LE. 0) then

           ! If no colons, check for hour.

           ! Logic below assumes a null character or something else is after the hour
           ! if we do not find a null character add one so that it correctly parses time
           if (TimeUnits(strlen:strlen) /= char(0)) then
              TimeUnits = trim(TimeUnits)//char(0)
              strlen=len_trim(TimeUnits)
           endif
           lastspace = index(TRIM(TimeUnits), ' ', BACK=.TRUE.)
           if ((strlen-lastspace).eq.2 .or. (strlen-lastspace).eq.3) then
             hpos(1) = lastspace+1
             hpos(2) = strlen-1
             read (TimeUnits(hpos(1):hpos(2)), * ) hour
             min  = 0
             sec  = 0
           else
             hour = 0
             min  = 0
             sec  = 0
           endif

         else
           hpos(1) = firstcolon - 2
           hpos(2) = firstcolon - 1
           lastcolon =  index(TimeUnits, ':', BACK=.TRUE.)
           if ( lastcolon .EQ. firstcolon ) then
             mpos(1) = firstcolon + 1
             mpos(2) = firstcolon + 2
             read (TimeUnits(hpos(1):hpos(2)), * ) hour
             read (TimeUnits(mpos(1):mpos(2)), * ) min
             sec = 0
           else
             mpos(1) = firstcolon + 1
             mpos(2) = lastcolon - 1
             spos(1) = lastcolon + 1
             spos(2) = lastcolon + 2
             read (TimeUnits(hpos(1):hpos(2)), * ) hour
             read (TimeUnits(mpos(1):mpos(2)), * ) min
             read (TimeUnits(spos(1):spos(2)), * ) sec
           endif
         endif
      class default
         _FAIL("Time unit must be character in "//fname)
      end select
      call ESMF_TimeSet(unmodStartTime,yy=year,mm=month,dd=day,h=hour,m=min,s=sec,rc=status)
      _VERIFY(status)

      call this%get_coordinate_info('time',coordSize=tsize,rc=status)
      _VERIFY(status)
      allocate(tr_r64(tsize))
      allocate(tvec(tsize))
      ptr => var%get_coordinate_data()
      _ASSERT(associated(ptr),"time variable coordinate data not found in "//fname)
      select type (ptr)
      type is (real(kind=REAL64))
         tr_r64=ptr
      type is (real(kind=REAL32))
         tr_r64=ptr
      type is (integer(kind=INT64))
         tr_r64=ptr
      type is (integer(kind=INT32))
         tr_r64=ptr
      class default
         _FAIL("unsupported time variable type in "//fname)
      end select
      do i=1,tsize
        select case (trim(tUnits))
        case ("days")
           call ESMF_TimeIntervalSet(tint,d_r8=tr_r64(i),rc=status)
           _VERIFY(status)
           tvec(i)=unmodStartTime+tint
        case ("hours")
           call ESMF_TimeIntervalSet(tint,h_r8=tr_r64(i),rc=status)
           _VERIFY(status)
           tvec(i)=unmodStartTime+tint
        case ("minutes")
           call ESMF_TimeIntervalSet(tint,m_r8=tr_r64(i),rc=status)
           _VERIFY(status)
           tvec(i)=unmodStartTime+tint
        case ("seconds")
           call ESMF_TimeIntervalSet(tint,s_r8=tr_r64(i),rc=status)
           _VERIFY(status)
           tvec(i)=unmodStartTime+tint
        case default
           _FAIL("unsupported time unit in "//fname)
        end select
      enddo

      call ESMF_TimeGet(tVec(1),yy=year,mm=month,dd=day,h=hour,m=min,s=sec,rc=status)
      _VERIFY(status)
      if (present(startYear)) startYear=year
      if (present(startMonth)) startMonth=month
      if (present(startDay)) startDay=day
      if (present(startHour)) startHour=hour
      if (present(startmin)) startMin=min
      if (present(startsec)) startSec=sec
      if (present(startTime)) then
          startTime=tVec(1)
      end if
      if (present(timeVector)) then
         allocate(timeVector,source=tVec,stat=status)
         _VERIFY(status)
      end if
      _RETURN(_SUCCESS)

   end subroutine get_time_info