ESMF_TimeIntervalSetDurStart Subroutine

private subroutine ESMF_TimeIntervalSetDurStart(timeinterval, startTime, keywordEnforcer, yy, yy_i8, mm, mm_i8, d, d_i8, h, m, s, s_i8, ms, us, ns, d_r8, h_r8, m_r8, s_r8, ms_r8, us_r8, ns_r8, sN, sN_i8, sD, sD_i8, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_TimeInterval), intent(inout) :: timeinterval
type(ESMF_Time), intent(in) :: startTime
type(ESMF_KeywordEnforcer), optional :: keywordEnforcer
integer(kind=ESMF_KIND_I4), intent(in), optional :: yy
integer(kind=ESMF_KIND_I8), intent(in), optional :: yy_i8
integer(kind=ESMF_KIND_I4), intent(in), optional :: mm
integer(kind=ESMF_KIND_I8), intent(in), optional :: mm_i8
integer(kind=ESMF_KIND_I4), intent(in), optional :: d
integer(kind=ESMF_KIND_I8), intent(in), optional :: d_i8
integer(kind=ESMF_KIND_I4), intent(in), optional :: h
integer(kind=ESMF_KIND_I4), intent(in), optional :: m
integer(kind=ESMF_KIND_I4), intent(in), optional :: s
integer(kind=ESMF_KIND_I8), intent(in), optional :: s_i8
integer(kind=ESMF_KIND_I4), intent(in), optional :: ms
integer(kind=ESMF_KIND_I4), intent(in), optional :: us
integer(kind=ESMF_KIND_I4), intent(in), optional :: ns
real(kind=ESMF_KIND_R8), intent(in), optional :: d_r8
real(kind=ESMF_KIND_R8), intent(in), optional :: h_r8
real(kind=ESMF_KIND_R8), intent(in), optional :: m_r8
real(kind=ESMF_KIND_R8), intent(in), optional :: s_r8
real(kind=ESMF_KIND_R8), intent(in), optional :: ms_r8
real(kind=ESMF_KIND_R8), intent(in), optional :: us_r8
real(kind=ESMF_KIND_R8), intent(in), optional :: ns_r8
integer(kind=ESMF_KIND_I4), intent(in), optional :: sN
integer(kind=ESMF_KIND_I8), intent(in), optional :: sN_i8
integer(kind=ESMF_KIND_I4), intent(in), optional :: sD
integer(kind=ESMF_KIND_I8), intent(in), optional :: sD_i8
integer, intent(out), optional :: rc

Source Code

      subroutine ESMF_TimeIntervalSetDurStart(timeinterval, startTime, &
        keywordEnforcer, &
        yy, yy_i8, &
        mm, mm_i8, &
        d, d_i8, &
        h, m, &
        s, s_i8, &
        ms, us, ns, &
        d_r8, h_r8, m_r8, s_r8, &
        ms_r8, us_r8, ns_r8, &
        sN, sN_i8, sD, sD_i8, &
        rc)

! !ARGUMENTS:
      type(ESMF_TimeInterval), intent(inout)         :: timeinterval
      type(ESMF_Time),         intent(in)            :: startTime
      type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
      integer(ESMF_KIND_I4),   intent(in),  optional :: yy
      integer(ESMF_KIND_I8),   intent(in),  optional :: yy_i8
      integer(ESMF_KIND_I4),   intent(in),  optional :: mm
      integer(ESMF_KIND_I8),   intent(in),  optional :: mm_i8
      integer(ESMF_KIND_I4),   intent(in),  optional :: d
      integer(ESMF_KIND_I8),   intent(in),  optional :: d_i8
      integer(ESMF_KIND_I4),   intent(in),  optional :: h
      integer(ESMF_KIND_I4),   intent(in),  optional :: m
      integer(ESMF_KIND_I4),   intent(in),  optional :: s
      integer(ESMF_KIND_I8),   intent(in),  optional :: s_i8
      integer(ESMF_KIND_I4),   intent(in),  optional :: ms
      integer(ESMF_KIND_I4),   intent(in),  optional :: us
      integer(ESMF_KIND_I4),   intent(in),  optional :: ns
      real(ESMF_KIND_R8),      intent(in),  optional :: d_r8
      real(ESMF_KIND_R8),      intent(in),  optional :: h_r8
      real(ESMF_KIND_R8),      intent(in),  optional :: m_r8
      real(ESMF_KIND_R8),      intent(in),  optional :: s_r8
      real(ESMF_KIND_R8),      intent(in),  optional :: ms_r8
      real(ESMF_KIND_R8),      intent(in),  optional :: us_r8
      real(ESMF_KIND_R8),      intent(in),  optional :: ns_r8
      integer(ESMF_KIND_I4),   intent(in),  optional :: sN
      integer(ESMF_KIND_I8),   intent(in),  optional :: sN_i8
      integer(ESMF_KIND_I4),   intent(in),  optional :: sD
      integer(ESMF_KIND_I8),   intent(in),  optional :: sD_i8
      integer,                 intent(out), optional :: rc

!
! !STATUS:
! \begin{itemize}
! \item\apiStatusCompatibleVersion{5.2.0r}
! \end{itemize}
!
! !DESCRIPTION:
!     Sets the value of the {\tt ESMF\_TimeInterval} in units specified by
!     the user via Fortran optional arguments.
!
!     The ESMF Time Manager represents and manipulates time internally with
!     integers to maintain precision.  Hence, user-specified floating point
!     values are converted internally to integers.
!
!     Ranges are limited only by machine word size.  Numeric defaults are 0,
!     except for sD, which is 1.
!
!     The arguments are:
!     \begin{description}
!     \item[timeinterval]
!          The object instance to initialize.
!     \item[startTime]
!          Starting time of an absolute calendar interval 
!          (yy, mm, and/or d); pins a calendar interval to a specific point 
!          in time.  If not set, and calendar also not set, calendar interval 
!          "floats" across all calendars and times.
!     \item[{[yy]}]
!          Integer year (32-bit).  Default = 0.
!     \item[{[yy\_i8]}]
!          Integer year (large, 64-bit).  Default = 0.
!     \item[{[mm]}]
!          Integer month (32-bit).  Default = 0.
!     \item[{[mm\_i8]}]
!          Integer month (large, 64-bit).  Default = 0.
!     \item[{[d]}]
!          Integer Julian day, or Modified Julian day (32-bit).  Default = 0.
!     \item[{[d\_i8]}]
!          Integer Julian day, or Modified Julian day (large, 64-bit).
!          Default = 0.
!     \item[{[h]}]
!          Integer hour.  Default = 0.
!     \item[{[m]}]
!          Integer minute.  Default = 0.
!     \item[{[s]}]
!          Integer second (32-bit).  Default = 0.
!     \item[{[s\_i8]}]
!          Integer second (large, 64-bit).  Default = 0.
!     \item[{[ms]}]
!          Integer millisecond.  Default = 0.
!     \item[{[us]}]
!          Integer microsecond.  Default = 0.
!     \item[{[ns]}]
!          Integer nanosecond.  Default = 0.
!     \item[{[d\_r8]}]
!          Double precision day.  Default = 0.0.
!     \item[{[h\_r8]}]
!          Double precision hour.  Default = 0.0.
!     \item[{[m\_r8]}]
!          Double precision minute.  Default = 0.0.
!     \item[{[s\_r8]}]
!          Double precision second.  Default = 0.0.
!     \item[{[ms\_r8]}]
!          Double precision millisecond.  Default = 0.0.
!     \item[{[us\_r8]}]
!          Double precision microsecond.  Default = 0.0.
!     \item[{[ns\_r8]}]
!          Double precision nanosecond.  Default = 0.0.
!     \item[{[sN]}]
!          Integer numerator of fractional second (sN/sD).
!          Default = 0.
!     \item[{[sN\_i8]}]
!          Integer numerator of fractional second (sN\_i8/sD\_i8)
!                                                           (large, 64-bit).
!          Default = 0.
!     \item[{[sD]}]
!          Integer denominator of fractional second (sN/sD).
!          Default = 1.
!     \item[{[sD\_i8]}]
!          Integer denominator of fractional second (sN\_i8/sD\_i8).
!                                                           (large, 64-bit).
!          Default = 1.
!     \item[{[rc]}]
!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!     \end{description}
!
!EOP
! !REQUIREMENTS:
!     TMGn.n.n
      integer :: localrc                        ! local return code

      ! Assume failure until success
      if (present(rc)) rc = ESMF_RC_NOT_IMPL
      localrc = ESMF_RC_NOT_IMPL

      ! check input
      ESMF_INIT_CHECK_SHALLOW(ESMF_TimeGetInit,startTime,rc)

      ! use optional args for any subset
      call c_ESMC_TimeIntervalSetDurStart(timeinterval, yy, yy_i8, &
                                          mm, mm_i8, &
                                          d, d_i8, h, m, s, s_i8, ms, &
                                          us, ns, d_r8, h_r8, m_r8, s_r8, &
                                          ms_r8, us_r8, ns_r8, &
                                          sN, sN_i8, sD, sD_i8, &
                                          startTime, localrc)
      if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
        ESMF_CONTEXT, rcToReturn=rc)) return

      ! mark output variable as successfully initialized
      call ESMF_TimeIntervalInit(timeinterval)

      ! Return success
      if (present(rc)) rc = ESMF_SUCCESS
      end subroutine ESMF_TimeIntervalSetDurStart