ESMF_ClockAdvance Subroutine

public subroutine ESMF_ClockAdvance(clock, keywordEnforcer, timeStep, ringingAlarmList, ringingAlarmCount, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Clock), intent(inout) :: clock
type(ESMF_KeywordEnforcer), optional :: keywordEnforcer
type(ESMF_TimeInterval), intent(in), optional :: timeStep
type(ESMF_Alarm), intent(out), optional :: ringingAlarmList(:)
integer, intent(out), optional :: ringingAlarmCount
integer, intent(out), optional :: rc

Source Code

      subroutine ESMF_ClockAdvance(clock, keywordEnforcer, &
        timeStep, ringingAlarmList, ringingAlarmCount, rc)

! !ARGUMENTS:
      type(ESMF_Clock),        intent(inout)         :: clock
      type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
      type(ESMF_TimeInterval), intent(in),  optional :: timeStep
      type(ESMF_Alarm),        intent(out), optional :: ringingAlarmList(:)
      integer,                 intent(out), optional :: ringingAlarmCount
      integer,                 intent(out), optional :: rc
!
!
! !STATUS:
! \begin{itemize}
! \item\apiStatusCompatibleVersion{5.2.0r}
! \end{itemize}
!
! !DESCRIPTION:
!     \begin{sloppypar}
!     Advances the {\tt clock}'s current time by one time step:  either the
!     {\tt clock}'s, or the passed-in {\tt timeStep} (see below).  When the
!     {\tt clock} is in {\tt ESMF\_DIRECTION\_FORWARD} (default), this method
!     adds the {\tt timeStep} to the {\tt clock}'s current time.
!     In {\tt ESMF\_DIRECTION\_REVERSE}, {\tt timeStep} is subtracted from the
!     current time.  In either case, {\tt timeStep} can be positive or negative.
!     See the "direction" argument in method {\tt ESMF\_ClockSet()}.
!     {\tt ESMF\_ClockAdvance()} optionally returns a list and number of ringing
!     {\tt ESMF\_Alarm}s.  See also method {\tt ESMF\_ClockGetRingingAlarms()}.
!     \end{sloppypar}
!
!     The arguments are:
!     \begin{description}
!     \item[clock]
!          The object instance to advance.
!     \item[{[timeStep]}]
!          Time step is performed with given timeStep, instead of
!          the {\tt ESMF\_Clock}'s.  Does not replace the {\tt ESMF\_Clock}'s
!          timeStep; use {\tt ESMF\_ClockSet(clock, timeStep, ...)} for
!          this purpose.  Supports applications with variable time steps.
!          timeStep can be positive or negative.
!     \item[{[ringingAlarmList]}]
!          Returns the array of alarms that are ringing after the
!          time step.
!     \item[{[ringingAlarmCount]}]
!          The number of alarms ringing after the time step.
!     \item[{[rc]}]
!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!     \end{description}
!
!EOP
! !REQUIREMENTS:
!     TMG3.4.1


      ! initialize list size to zero for not-present list
      integer :: sizeofRingingAlarmList,i
      type(ESMF_Pointer), allocatable :: ringingAlarmPtrList(:)
      integer :: localrc                        ! local return code

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

      ! check inputs
      ESMF_INIT_CHECK_DEEP(ESMF_ClockGetInit,clock,rc)
      ESMF_INIT_CHECK_SHALLOW(ESMF_TimeIntervalGetInit,timeStep,rc)

      sizeofRingingAlarmList = 0

      ! get size of given ringing alarm list for C++ validation
      if (present(ringingAlarmList)) then
        sizeofRingingAlarmList = size(ringingAlarmList)

        ! for Init Macros
        allocate(ringingAlarmPtrList(sizeofRingingAlarmList))
      end if

      ! invoke C to C++ entry point

      if (present(ringingAlarmList) .and. sizeofRingingAlarmList > 1) then
        ! pass address of 2nd element for C++ to calculate array step size
        call c_ESMC_ClockAdvance2(clock, timeStep, &
                     ringingAlarmPtrList(1), ringingAlarmPtrList(2), &
                     sizeofRingingAlarmList, ringingAlarmCount, localrc)
        if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
          ESMF_CONTEXT, rcToReturn=rc)) then
          ! Not bail out until deallocation
          write(*,*)"c_ESMC_ClockAdvance2 fails"
        endif
      else if (sizeofRingingAlarmList == 1) then
        ! array has only one element
        call c_ESMC_ClockAdvance1(clock, timeStep, ringingAlarmPtrList(1), &
                        sizeofRingingAlarmList, ringingAlarmCount, localrc)
        ! Not bail out until deallocation
        if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
          ESMF_CONTEXT, rcToReturn=rc)) then
          ! Not bail out until deallocation
          write(*,*)"c_ESMC_ClockAdvance1 fails"
        endif
      else
        ! array is not present
        call c_ESMC_ClockAdvance0(clock, timeStep, &
                    sizeofRingingAlarmList, ringingAlarmCount, localrc)
        if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
          ESMF_CONTEXT, rcToReturn=rc)) then
          ! Not bail out until deallocation
          write(*,*)"c_ESMC_ClockAdvance0 fails"
        endif
      endif

      ! post-process ringing alarm list
      if (present(ringingAlarmList)) then
         do i=1,sizeofRingingAlarmList
            call ESMF_AlarmSetThis(ringingAlarmList(i),ringingAlarmPtrList(i))
            ! mark output as successfully initialized
            call ESMF_AlarmSetInitCreated(ringingAlarmList(i))
         enddo

        ! Get rid of list
        deallocate(ringingAlarmPtrList)
     end if

     ! Return success
     if (present(rc)) rc = localrc

     end subroutine ESMF_ClockAdvance