GetDateTimeVec Subroutine

public subroutine GetDateTimeVec(fid, begDate, begTime, incVec, rc)

GetDateTimeVec - Get date/time of file samples

This routine returns the date/times on file.

History

  • 1999.11.01 da Silva Initial code.
  • 1999.11.08 da Silva Generic time coordinate variable (no name assumed).
  • 2000.10.18 Lucchesi Added ParseTimeUnits subroutine to handle a wider variety of Units formats.
  • 2016.12.06 Eastham Adapted to return the vector of offsets instead

Arguments

Type IntentOptional Attributes Name
integer :: fid

file ID

integer :: begDate

Beginning date

integer :: begTime

Beginning time

integer(kind=INT64) :: incVec(:)

Vector of offsets (seconds)

integer :: rc

error return code


Calls

proc~~getdatetimevec~~CallsGraph proc~getdatetimevec GetDateTimeVec interface~getdate GetDate proc~getdatetimevec->interface~getdate nf90_get_att nf90_get_att proc~getdatetimevec->nf90_get_att nf90_get_var nf90_get_var proc~getdatetimevec->nf90_get_var nf90_inq_varid nf90_inq_varid proc~getdatetimevec->nf90_inq_varid nf90_inquire nf90_inquire proc~getdatetimevec->nf90_inquire nf90_inquire_dimension nf90_inquire_dimension proc~getdatetimevec->nf90_inquire_dimension nf90_inquire_variable nf90_inquire_variable proc~getdatetimevec->nf90_inquire_variable proc~err err proc~getdatetimevec->proc~err proc~identifydim IdentifyDim proc~getdatetimevec->proc~identifydim proc~parsetimeunits ParseTimeUnits proc~getdatetimevec->proc~parsetimeunits proc~getdateint4 GetDateInt4 interface~getdate->proc~getdateint4 proc~getdateint8 GetDateInt8 interface~getdate->proc~getdateint8 proc~getdateint4->proc~getdateint8 proc~caldat CALDAT proc~getdateint8->proc~caldat proc~cfio_parseinttime CFIO_parseIntTime proc~getdateint8->proc~cfio_parseinttime proc~julday julday proc~getdateint8->proc~julday

Called by

proc~~getdatetimevec~~CalledByGraph proc~getdatetimevec GetDateTimeVec proc~cfio_getvar CFIO_GetVar proc~cfio_getvar->proc~getdatetimevec proc~cfio_sgetvar CFIO_SGetVar proc~cfio_sgetvar->proc~getdatetimevec

Source Code

      subroutine GetDateTimeVec ( fid, begDate, begTime, incVec, rc )
!
! !USES:
!
      Implicit NONE
!
! !INPUT PARAMETERS:
!
      integer fid      !! file ID
!
! !OUTPUT PARAMETERS:
!
      integer               :: begDate   !! Beginning date
      integer               :: begTime   !! Beginning time
      integer(Kind=INT64) :: incVec(:) !! Vector of offsets (seconds)
      integer               :: rc        !! error return code
!
!-------------------------------------------------------------------------

      integer i, timeId, hour, min, sec, corner(1)
      !integer incSecs
      integer year, month, day
      character(len=MAXCHR) timeUnits, dimUnits
      !character(len=MAXCHR) strTmp

      character(len=MAXCHR) varName, dimName, stdName
      integer type, nvDims, vdims(MAXVDIMS), nvAtts, dimSize
      integer nDims, nvars, ngatts, dimId

!     Time conversion local variables
      real(kind=REAL32)    rtime, rtime_array(1)
      real(kind=REAL64)    dtime, dtime_array(1)
      integer(kind=INT16) itime, itime_array(1)
      integer(kind=REAL32) ltime, ltime_array(1)
      !integer   t1
      integer   newDate, newTime

!     We now have the possibility of a very large interval
      integer(Kind=INT64) :: t1Long, t2Long, tMultLong, incSecsLong
      integer(Kind=INT64),allocatable :: incVecLong(:) ! Vector of offsets (seconds)

!     Get the starting date and time
!     ---------------------------------------------------------

!     Start by determing the ID of the time coordinate variable
!     ---------------------------------------------------------
      timeId = -1
      rc = NF90_INQUIRE (fid, nDims, nvars, ngatts, dimId)
      if (err("GetDateTimeVec: NF90_INQUIRE failed",rc,-48) .NE. 0)return
      do i=1,nDims
        rc = NF90_INQUIRE_DIMENSION (fid, i, dimName, dimSize)
        if (err("GetDateTimeVec: can't get dim info",rc,-41) .NE. 0) return
        if (index(dimName,'station')  .gt. 0) cycle
        if (trim(dimName) .eq. 'nv') cycle
        if ( index(dimName,'edges') .gt. 0 ) cycle

        if (trim(dimName) .eq. 'nv') cycle
        if (trim(dimName) .eq. 'nf') cycle
        if (trim(dimName) .eq. 'ncontact') cycle
        if (trim(dimName) .eq. 'XCdim') cycle
        if (trim(dimName) .eq. 'YCdim') cycle
        if (trim(dimName) .eq. 'orientationStrLen') cycle

        rc = NF90_INQ_VARID (fid, dimName, dimId)
        if (err("GetDateTimeVec: NF90_INQ_VARID failed",rc,-40) .NE. 0) return
        ! If it has the standard_name attribute, use that instead
        rc = NF90_GET_ATT(fid,dimId,'standard_name',stdName)
        if (rc .ne. 0) stdName = Trim(dimName)
        rc = NF90_GET_ATT(fid,dimId,'units',dimUnits)
        if (err("GetDateTimeVec: could not get units for dimension",rc,-53)&
            .NE. 0) return
        if ( IdentifyDim (stdName, dimUnits) .eq. 3 ) then
             timeId = dimId
             timeUnits = dimUnits
             exit
        end if
      end do

      if ( timeId .lt. 0 ) then
         rc = -43
         print *, "GetDateTimeVec: could not find time coord"
         return
      end if

!     Attempt to parse the COARDS compliant time units
!     --------------------------------------------------
!ams      rc = NF90_GET_ATT(fid,timeId,'units',timeUnits)
!ams      if (err("GetDateTimeVec: missing time.units",rc,-44) .NE. 0) return
      i = index(timeUnits,'since')
      if ( i .le. 0 ) then
          if (err("GetDateTimeVec: invalid time units",1,-44) .NE. 0) return
      endif

!     Call to ParseTimeUnits replaces an internal read, that made assumptions
!     about the format of the Time Units string that were not always true.
!     (RL: 10/2000)

      call ParseTimeUnits ( timeUnits, year, month, day, hour, min, sec, rc )
      begDate = year*10000 + month*100 + day
      begTime = hour*10000 + min*100   + sec

!     Retreive time vector.
!     -------------------------
      rc = NF90_INQUIRE_VARIABLE (fid, timeID, varName, type, nvDims, vDims, &
          nvAtts)
      if (err("GetDateTimeVec: error in time variable inquire",&
         rc,-52) .NE. 0) return

      allocate(incVecLong(dimSize))
      incVecLong(:) = 0
      do i=1,dimsize
           if ( type .eq. NF90_FLOAT )  then
                corner(1) = i
                rc = NF90_GET_VAR(fid,timeID,rtime_array,corner,(/1/))
                rtime = rtime_array(1)
                incVecLong(i) = int(rtime,INT64)
           else if ( type .eq. NF90_DOUBLE ) then
                corner(1) = i
                rc = NF90_GET_VAR(fid,timeID,dtime_array,corner,(/1/))
                dtime = dtime_array(1)
                incVecLong(i) = int(dtime,INT64)
           else if ( type .eq. NF90_SHORT  ) then
                corner(1) = i
                rc = NF90_GET_VAR(fid,timeID,itime_array,corner,(/1/))
                itime = itime_array(1)
                incVecLong(i) = int(itime,INT64)
           else if ( type .eq. NF90_INT   ) then
                corner(1) = i
                rc = NF90_GET_VAR(fid,timeID,ltime_array,corner,(/1/))
                ltime = ltime_array(1)
                incVecLong(i) = int(ltime,INT64)
           else
                if (err("GetDateTimeVec: invalid time data type",&
                   1,-44) .NE. 0) return
           endif
      end do

!     Convert time increment to seconds if necessary
!     ----------------------------------------------
      if ( timeUnits(1:6) .eq.  'minute' ) then
           tMultLong = 60
      else if ( timeUnits(1:4) .eq. 'hour'   ) then
           tMultLong = 60 * 60
      else if ( timeUnits(1:3) .eq.  'day' ) then
           tMultLong = 60 * 60 * 24
      else
           if (err("GetDateTimeVec: invalid time unit name",&
              1,-44) .NE. 0) return
      endif

!     Combine the first time offset with the reference time to get the beginning
!     date and time
!     -----------------------------------------------------------------------------
      t1Long = incVecLong(1)
      Call GetDate(begDate,begTime,t1Long*tMultLong,newDate,newTime,rc)
      begDate=newDate
      begTime=newTime

!     Convert all the offsets to reference the first sample
!     -----------------------------------------------------------------------------
      incVec(:) = 0
      do i=1,dimsize
         t2Long = incVecLong(i)
         incSecsLong = (t2Long - t1Long)*tMultLong
         ! If (incSecsLong.gt.huge(t1)) Then
         !   print *, 'Time interval too large'
         !   rc = -10
         !   return
         ! End If
         ! Sometimes we actually do need to return this as a longlong..
         !incSecs = int(incSecsLong,4)
         !incVec(i) = incSecs
         incVec(i) = incSecsLong
      end do
      deallocate(incVecLong)
!ams  print *, 'begdate, begtime, incsecs: ',begdate, begtime, incsecs

      rc = 0 ! all done

      return
      end subroutine GetDateTimeVec