GetFirstDate Function

public function GetFirstDate(filename) result(time)

Uses

given filename of a multidimensional net-cdf file the GetFirstDate function returns the date and time of first grid

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename

Return Value type(DateTime)


Variables

Type Visibility Attributes Name Initial
character(len=80), public :: attribute
integer, public :: dt
integer(kind=short), public :: i
integer(kind=short), public :: idTime

Id of the variable containing information on time coordinate

integer(kind=short), public :: nAtts

number of global attributes

integer(kind=short), public :: nDims

number of dimensions

integer(kind=short), public :: nVars

number of variables

integer(kind=short), public :: ncId

NetCdf Id for the file

integer(kind=short), public :: ncStatus

error code returned by NetCDF routines

type(DateTime), public :: ref_time
integer, public :: slice(1)
integer, public :: slice2(2)
character(len=19), public :: str
integer, public :: time1
character(len=7), public :: time_unit
character(len=100), public :: variableName

Source Code

FUNCTION GetFirstDate &
!
(filename) &
!
RESULT (time)

USE Chronos, ONLY: &
!Imported type definitions:
DateTime

USE Units, ONLY: &
! Imported parameters:
minute, hour, day, month

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT(IN) :: filename

!Local declarations:
TYPE (DateTime)  :: time
INTEGER (KIND = short) :: ncStatus !!error code returned by NetCDF routines
INTEGER (KIND = short) :: ncId  !!NetCdf Id for the file
TYPE(DateTime)         :: ref_time
CHARACTER (LEN = 7)    :: time_unit
INTEGER (KIND = short) :: idTime !!Id of the variable containing 
                                 !!information on time coordinate 
INTEGER (KIND = short) :: nDims !!number of dimensions
INTEGER (KIND = short) :: nVars !!number of variables
INTEGER (KIND = short) :: nAtts !!number of global attributes
CHARACTER (LEN = 80)   :: attribute
CHARACTER (LEN = 100)  :: variableName
INTEGER                :: slice (1)
INTEGER                :: slice2 (2)
INTEGER                :: time1
INTEGER                :: dt
INTEGER (KIND = short) :: i
CHARACTER (LEN = 19)   :: str
!------------end of declaration------------------------------------------------

!open net-cdf file with read-only access
ncStatus = nf90_open (fileName, NF90_NOWRITE, ncId)
IF (ncStatus /= nf90_noerr) THEN
  CALL Catch ('error', 'GridLib',        &
  TRIM (nf90_strerror (ncStatus) )//': ',  &
  code = ncIOError, argument = fileName )
ENDIF

!retrieve time unit
CALL ParseTime (ncId, ref_time, time_unit)

!inquire dataset to retrieve number of dimensions, variables 
!and global attributes
ncStatus = nf90_inquire(ncId, nDimensions = nDims, &
                        nVariables = nVars,        &
                        nAttributes = nAtts        )
                  
CALL ncErrorHandler (ncStatus)

!search for time variable
DO i = 1, nVars
  attribute = ''
  ncStatus = nf90_get_att (ncId, varid = i, name = 'standard_name', &
                           values = attribute)
  
  IF (ncStatus == nf90_noerr) THEN !standard_name is defined
    IF ( attribute(1:4) == 'time' ) THEN
      idTime = i 
      EXIT   
    END IF
  ELSE !standard_name is not defined: search for variable named 'time'
     !ncStatus = nf90_inq_varid (ncId, 'time', varid = i )
     ncstatus = nf90_inquire_variable(ncId, varId = i, name = variableName)
     IF (LEN_TRIM(variableName) == 4 .AND. &
         variableName(1:4) == 'time' .OR. &
         LEN_TRIM(variableName) == 5 .AND. &
         variableName(1:5) == 'Times' ) THEN !variable 'time' found
       idTime = i 
       EXIT 
     END IF
  END IF
END DO

IF (DateTimeIsDefault(ref_time)) THEN
   slice2(1) = 1
   slice2(2) = 1
   ncStatus = nf90_get_var (ncId, idTime, str , start = slice2)
   CALL ncErrorHandler (ncStatus)
   !build datetime string from format used in netcdf file i.e 2007-10-11_00:00:00
   timeString = str(1:10) // 'T' // str(12:19) // '+00:00'
   time = timeString
  
ELSE
    !retrieve timespan of first grid 
    slice(1) = 1
    ncStatus = nf90_get_var (ncId, idTime, time1 , start = slice)
    CALL ncErrorHandler (ncStatus)

    dt = time1

    !convert in seconds
    SELECT CASE (time_unit)
      CASE ('minutes')
        dt = dt * minute
      CASE ('hours')
        dt = dt * hour
      CASE ('days')
        dt = dt * day
      CASE ('months')
        dt = dt * month
    END SELECT
    
    !compute time

    time = ref_time + dt

END IF

RETURN

END FUNCTION GetFirstDate