ESMF_ClockGetAlarmList Subroutine

public subroutine ESMF_ClockGetAlarmList(clock, alarmlistflag, keywordEnforcer, timeStep, alarmList, alarmCount, rc)

Arguments

Type IntentOptional Attributes Name
type(ESMF_Clock), intent(in) :: clock
type(ESMF_AlarmList_Flag), intent(in) :: alarmlistflag
type(ESMF_KeywordEnforcer), optional :: keywordEnforcer
type(ESMF_TimeInterval), intent(in), optional :: timeStep
type(ESMF_Alarm), intent(out), optional :: alarmList(:)
integer, intent(out), optional :: alarmCount
integer, intent(out), optional :: rc

Source Code

      subroutine ESMF_ClockGetAlarmList(clock, alarmlistflag, &
        keywordEnforcer, timeStep, alarmList, alarmCount, rc)

! !ARGUMENTS:
      type(ESMF_Clock),          intent(in)            :: clock
      type(ESMF_AlarmList_Flag), intent(in)            :: alarmlistflag
      type(ESMF_KeywordEnforcer), optional:: keywordEnforcer ! must use keywords below
      type(ESMF_TimeInterval),   intent(in),  optional :: timeStep
      type(ESMF_Alarm),          intent(out), optional :: alarmList(:)
      integer,                   intent(out), optional :: alarmCount
      integer,                   intent(out), optional :: rc
!
!
! !STATUS:
! \begin{itemize}
! \item\apiStatusCompatibleVersion{5.2.0r}
! \end{itemize}
!
! !DESCRIPTION:
!     Gets the {\tt clock}'s list of alarms and/or number of alarms.
!
!     The arguments are:
!     \begin{description}
!     \item[clock]
!          The object instance from which to get an {\tt ESMF\_Alarm} list
!          and/or count of {\tt ESMF\_Alarm}s.
!     \item[alarmlistflag]
!          The kind of list to get:
!
!            {\tt ESMF\_ALARMLIST\_ALL} :
!                Returns the {\tt ESMF\_Clock}'s entire list of alarms.
!
!            {\tt ESMF\_ALARMLIST\_NEXTRINGING} :
!                Return only those alarms that will ring upon the next
!                {\tt clock} time step.  Can optionally specify argument
!                {\tt timeStep} (see below) to use instead of the {\tt clock}'s.
!                See also method {\tt ESMF\_AlarmWillRingNext()} for checking a
!                single alarm.
!
!            {\tt ESMF\_ALARMLIST\_PREVRINGING} :
!                \begin{sloppypar}
!                Return only those alarms that were ringing on the previous
!                {\tt ESMF\_Clock} time step.  See also method
!                {\tt ESMF\_AlarmWasPrevRinging()} for checking a single alarm.
!                \end{sloppypar}
!
!            {\tt ESMF\_ALARMLIST\_RINGING} :
!                Returns only those {\tt clock} alarms that are currently
!                ringing.  See also method {\tt ESMF\_ClockAdvance()} for
!                getting the list of ringing alarms subsequent to a time step.
!                See also method {\tt ESMF\_AlarmIsRinging()} for checking a
!                single alarm.
!     \item[{[timeStep]}]
!          \begin{sloppypar}
!          Optional time step to be used instead of the {\tt clock}'s.
!          Only used with {\tt ESMF\_ALARMLIST\_NEXTRINGING alarmlistflag}
!          (see above); ignored if specified with other {\tt alarmlistflags}.
!          \end{sloppypar}
!     \item[{[alarmList]}]
!          The array of returned alarms.  If given, the array must be large
!          enough to hold the number of alarms of the specified
!          {\tt alarmlistflag} in the specified {\tt clock}.
!     \item[{[alarmCount]}]
!          If specified, returns the number of {\tt ESMF\_Alarm}s of the
!          specified {\tt alarmlistflag} in the specified {\tt clock}.
!     \item[{[rc]}]
!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
!     \end{description}
!
!EOP
! !REQUIREMENTS:
!     TMG4.3, 4.8

      ! get size of given alarm list for C++ validation
      integer :: sizeofAlarmList,i
      type(ESMF_Pointer), allocatable :: alarmPtrList(:)
      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)

      if (.not.present(alarmList)) then
        ! only get alarmCount if specified
        sizeofAlarmList = 0
        ! invoke C to C++ entry point
        call c_ESMC_ClockGetAlarmList3(clock, alarmlistflag, &
                           sizeofAlarmList, alarmCount, timeStep, localrc)
        if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
          ESMF_CONTEXT, rcToReturn=rc)) return
      else
        ! get alarmList and alarmCount if specified

        sizeofAlarmList = size(alarmList)

        ! for init macros
        allocate(alarmPtrList(sizeofAlarmList))

        ! invoke C to C++ entry point
        if (sizeofAlarmList > 1) then
          ! pass address of 2nd element for C++ to calculate array step size
          call c_ESMC_ClockGetAlarmList2(clock, alarmlistflag, &
                             alarmPtrList(1), alarmPtrList(2), &
                             sizeofAlarmList, alarmCount, timeStep, localrc)
          if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) then
            ! do not bail out until deallocation
            write(*,*)"c_ESMC_ClockGetAlarmList2 fails"
          endif
        else
          ! array has only one element
          call c_ESMC_ClockGetAlarmList1(clock, alarmlistflag, &
                             alarmPtrList(1), &
                             sizeofAlarmList, alarmCount, timeStep, localrc)
          if (ESMF_LogFoundError(localrc, ESMF_ERR_PASSTHRU, &
            ESMF_CONTEXT, rcToReturn=rc)) then
            ! do not bail out until deallocation
            write(*,*)"c_ESMC_ClockGetAlarmList1 fails"
          endif
        endif

        ! post-process alarm list
        do i=1,sizeofAlarmList
           call ESMF_AlarmSetThis(alarmList(i),alarmPtrList(i))
           ! mark output as successfully initialized
           call ESMF_AlarmSetInitCreated(alarmList(i))
        enddo

        ! Get rid of temporary list
        deallocate(alarmPtrList)

      endif

      ! Return success
      if (present(rc)) rc = localrc
      end subroutine ESMF_ClockGetAlarmList