updated top-level README and version_decl for V4.4.2 (#1795)
[WRF.git] / external / esmf_time_f90 / ESMF_Alarm.F90
blobf25a2cc4f1160cb368961939e2081964e295976f
2 !==============================================================================
4 !     ESMF Alarm Module
5       module WRF_ESMF_AlarmMod
7 !==============================================================================
9 ! This file contains the Alarm class definition and all Alarm class 
10 ! methods.
12 !------------------------------------------------------------------------------
13 ! INCLUDES
14 #include <ESMF_TimeMgr.inc>
16 !===============================================================================
17 !BOPI
19 ! !MODULE: WRF_ESMF_AlarmMod
21 ! !DESCRIPTION:
22 ! Part of Time Manager F90 API wrapper of C++ implemenation
24 ! Defines F90 wrapper entry points for corresponding
25 ! C++ class {\tt ESMC\_Alarm}
27 ! See {\tt ../include/ESMC\_Alarm.h} for complete description
29 !------------------------------------------------------------------------------
30 ! !USES:
31       ! inherit from ESMF base class
32       use WRF_ESMF_BaseMod
34       ! associated derived types
35       use WRF_ESMF_TimeIntervalMod, only : ESMF_TimeInterval, &
36                                            ESMF_TimeIntervalAbsValue
37       use WRF_ESMF_TimeMod,         only : ESMF_Time
39       implicit none
41 !------------------------------------------------------------------------------
42 ! !PRIVATE TYPES:
43      private
44 !------------------------------------------------------------------------------
45 !     ! ESMF_Alarm
47 !     ! F90 class type to match C++ Alarm class in size only;
48 !     !  all dereferencing within class is performed by C++ implementation
50 ! internals for ESMF_Alarm
51       type ESMF_AlarmInt
52         type(ESMF_TimeInterval) :: RingInterval
53         type(ESMF_Time)  :: RingTime
54         type(ESMF_Time)  :: PrevRingTime
55         type(ESMF_Time)  :: StopTime
56         integer :: ID
57         integer :: AlarmMutex
58         logical :: Ringing
59         logical :: Enabled
60         logical :: RingTimeSet
61         logical :: RingIntervalSet
62         logical :: StopTimeSet
63       end type
65 ! Actual public type:  this bit allows easy mimic of "deep" ESMF_AlarmCreate
66 ! in ESMF 2.1.0+.  Note that ESMF_AlarmCreate is in a separate module to avoid 
67 ! cyclic dependence.  
68 ! NOTE:  DO NOT ADD NON-POINTER STATE TO THIS DATA TYPE.  It emulates ESMF 
69 !        shallow-copy-masquerading-as-reference-copy insanity.  
70       type ESMF_Alarm
71         type(ESMF_AlarmInt), pointer :: alarmint
72       end type
74 !------------------------------------------------------------------------------
75 ! !PUBLIC TYPES:
76       public ESMF_Alarm
77       public ESMF_AlarmInt   ! needed on AIX but not PGI
78 !------------------------------------------------------------------------------
80 ! !PUBLIC MEMBER FUNCTIONS:
81       public ESMF_AlarmDestroy
82       public ESMF_AlarmSet
83       public ESMF_AlarmGet
84 !      public ESMF_AlarmGetRingInterval
85 !      public ESMF_AlarmSetRingInterval
86 !      public ESMF_AlarmGetRingTime
87 !      public ESMF_AlarmSetRingTime
88 !      public ESMF_AlarmGetPrevRingTime
89 !      public ESMF_AlarmSetPrevRingTime
90 !      public ESMF_AlarmGetStopTime
91 !      public ESMF_AlarmSetStopTime
92       public ESMF_AlarmEnable
93       public ESMF_AlarmDisable
94       public ESMF_AlarmRingerOn
95       public ESMF_AlarmRingerOff
96       public ESMF_AlarmIsRinging
97 !      public ESMF_AlarmCheckRingTime
98       public operator(==)
100 ! Required inherited and overridden ESMF_Base class methods
102 !      public ESMF_AlarmRead
103 !      public ESMF_AlarmWrite
104       public ESMF_AlarmValidate
105       public ESMF_AlarmPrint
107 ! !PRIVATE MEMBER FUNCTIONS:
108       private ESMF_AlarmEQ
109 !EOPI
111 !==============================================================================
113 ! INTERFACE BLOCKS
115 !==============================================================================
116 !BOP
117 ! !INTERFACE:
118       interface operator(==)
120 ! !PRIVATE MEMBER FUNCTIONS:
121       module procedure ESMF_AlarmEQ
123 ! !DESCRIPTION:
124 !     This interface overloads the == operator for the {\tt ESMF\_Alarm} class
126 !EOP
127       end interface
129 !------------------------------------------------------------------------------
131 !==============================================================================
133       contains
135 !==============================================================================
137 !------------------------------------------------------------------------------
139 ! This section includes the Set methods.
141 !------------------------------------------------------------------------------
142 !BOP
143 ! !IROUTINE: ESMF_AlarmSet - Initializes an alarm
145 ! !INTERFACE:
146       subroutine ESMF_AlarmSet(alarm, RingTime, RingInterval, PrevRingTime, &
147                                StopTime, Enabled, rc)
149 ! !ARGUMENTS:
150       type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
151       type(ESMF_Time), intent(in), optional :: RingTime, PrevRingTime
152       type(ESMF_TimeInterval), intent(in), optional :: RingInterval
153       type(ESMF_Time), intent(in), optional :: StopTime
154       logical, intent(in), optional :: Enabled
155       integer, intent(out), optional :: rc
157 ! !DESCRIPTION:
158 !     Initializes an {\tt ESMF\_Alarm}
160 !     The arguments are:
161 !     \begin{description}
162 !     \item[alarm]
163 !          The object instance to initialize
164 !     \item[{[RingTime]}]
165 !          Optional ring time for one-shot or first repeating alarm
166 !     \item[{[RingInterval]}]
167 !          Optional ring interval for repeating alarms
168 !     \item[{[StopTime]}]
169 !          Optional stop time for repeating alarms
170 !     \item[Enabled]
171 !          Alarm enabled/disabled
172 !     \item[{[rc]}]
173 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
174 !     \end{description}
176 ! !REQUIREMENTS:
177 !     TMG4.1, TMG4.7
178 !EOP
179       IF ( ASSOCIATED( alarm%alarmint ) ) THEN
180         alarm%alarmint%RingTimeSet = .FALSE.
181         alarm%alarmint%RingIntervalSet = .FALSE.
182         alarm%alarmint%StopTimeSet = .FALSE.
183         IF ( PRESENT( RingInterval ) ) THEN
184           ! force RingInterval to be positive
185           alarm%alarmint%RingInterval = &
186             ESMF_TimeIntervalAbsValue( RingInterval )
187           alarm%alarmint%RingIntervalSet = .TRUE.
188         ENDIF
189         IF ( PRESENT( PrevRingTime ) ) THEN
190           alarm%alarmint%PrevRingTime = PrevRingTime
191         ENDIF
192         IF ( PRESENT( RingTime ) ) THEN
193           alarm%alarmint%RingTime = RingTime
194           alarm%alarmint%RingTimeSet = .TRUE.
195         ENDIF
196         IF ( PRESENT( StopTime ) ) THEN
197           alarm%alarmint%StopTime = StopTime
198           alarm%alarmint%StopTimeSet = .TRUE.
199         ENDIF
200         alarm%alarmint%Enabled = .TRUE.
201         IF ( PRESENT( Enabled ) ) THEN
202           alarm%alarmint%Enabled = Enabled
203         ENDIF
204         IF ( PRESENT( rc ) ) THEN
205           rc = ESMF_SUCCESS
206         ENDIF
207         alarm%alarmint%Ringing = .FALSE.
208         alarm%alarmint%Enabled = .TRUE.
209       ELSE
210         IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
211       ENDIF
213       end subroutine ESMF_AlarmSet
217 ! Deallocate memory for ESMF_Alarm
218       SUBROUTINE ESMF_AlarmDestroy( alarm, rc )
219          TYPE(ESMF_Alarm), INTENT(INOUT) :: alarm
220          INTEGER,          INTENT(  OUT), OPTIONAL :: rc
221          IF ( ASSOCIATED( alarm%alarmint ) ) THEN
222            DEALLOCATE( alarm%alarmint )
223          ENDIF
224          ! TBH:  ignore deallocate errors, for now
225          IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
226       END SUBROUTINE ESMF_AlarmDestroy
230 !------------------------------------------------------------------------------
231 !BOP
232 ! !IROUTINE: ESMF_AlarmGetRingInterval - Get an alarm's ring interval
234 ! !INTERFACE:
235       subroutine ESMF_AlarmGetRingInterval(alarm, RingInterval, rc)
237 ! !ARGUMENTS:
238       type(ESMF_Alarm), intent(in) :: alarm
239       type(ESMF_TimeInterval), intent(out) :: RingInterval
240       integer, intent(out), optional :: rc
242 ! !DESCRIPTION:
243 !     Get an {\tt ESMF\_Alarm}'s ring interval
245 !     The arguments are:
246 !     \begin{description}
247 !     \item[alarm]
248 !          The object instance to get the ring interval
249 !     \item[RingInterval]
250 !          The {\tt Alarm}'s ring interval
251 !     \item[{[rc]}]
252 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
253 !     \end{description}
255 ! !REQUIREMENTS:
256 !     TMG4.7
257 !EOP
258       RingInterval = alarm%alarmint%RingInterval
260       end subroutine ESMF_AlarmGetRingInterval
262 !------------------------------------------------------------------------------
263 !BOP
264 ! !IROUTINE: ESMF_AlarmSetRingInterval - Set an alarm's ring interval
266 ! !INTERFACE:
267       subroutine ESMF_AlarmSetRingInterval(alarm, RingInterval, rc)
269 ! !ARGUMENTS:
270       type(ESMF_Alarm), intent(out) :: alarm
271       type(ESMF_TimeInterval), intent(in) :: RingInterval
272       integer, intent(out), optional :: rc
274 ! !DESCRIPTION:
275 !     Set an {\tt ESMF\_Alarm}'s ring interval
277 !     The arguments are:
278 !     \begin{description}
279 !     \item[alarm]
280 !          The object instance to set the ring interval
281 !     \item[RingInterval]
282 !          The {\tt Alarm}'s ring interval
283 !     \item[{[rc]}]
284 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
285 !     \end{description}
287 ! !REQUIREMENTS:
288 !     TMG4.5.2, TMG4.7
289 !EOP
290       CALL wrf_error_fatal( 'ESMF_AlarmSetRingInterval not supported' )
291       end subroutine ESMF_AlarmSetRingInterval
293 !------------------------------------------------------------------------------
294 !BOP
295 ! !IROUTINE:  ESMF_AlarmGetRingTime - Get an alarm's time to ring
297 ! !INTERFACE:
298       subroutine ESMF_AlarmGetRingTime(alarm, RingTime, rc)
300 ! !ARGUMENTS:
301       type(ESMF_Alarm), intent(in) :: alarm
302       type(ESMF_Time), intent(out) :: RingTime
303       integer, intent(out), optional :: rc
305 ! !DESCRIPTION:
306 !     Get an {\tt ESMF\_Alarm}'s time to ring
308 !     The arguments are:
309 !     \begin{description}
310 !     \item[alarm]
311 !          The object instance to get the ring time
312 !     \item[RingTime]
313 !          The {\tt ESMF\_Alarm}'s ring time
314 !     \item[{[rc]}]
315 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
316 !     \end{description}
318 ! !REQUIREMENTS:
319 !     TMG4.7, TMG4.8
320 !EOP
321       CALL wrf_error_fatal( 'ESMF_AlarmGetRingTime not supported' )
322       end subroutine ESMF_AlarmGetRingTime
324 !------------------------------------------------------------------------------
325 !BOP
326 ! !IROUTINE:  ESMF_AlarmSetRingTime - Set an alarm's time to ring
328 ! !INTERFACE:
329       subroutine ESMF_AlarmSetRingTime(alarm, RingTime, rc)
331 ! !ARGUMENTS:
332       type(ESMF_Alarm), intent(out) :: alarm
333       type(ESMF_Time), intent(in) :: RingTime
334       integer, intent(out), optional :: rc
336 ! !DESCRIPTION:
337 !     Set an {\tt ESMF\_Alarm}'s time to ring
339 !     The arguments are:
340 !     \begin{description}
341 !     \item[alarm]
342 !          The object instance to set the ring time
343 !     \item[RingTime]
344 !          The {\tt ESMF\_Alarm}'s ring time to set
345 !     \item[{[rc]}]
346 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
347 !     \end{description}
349 ! !REQUIREMENTS:
350 !     TMG4.5.1, TMG4.7, TMG4.8
351 !EOP
352       CALL wrf_error_fatal( 'ESMF_AlarmSetRingTime not supported' )
353       end subroutine ESMF_AlarmSetRingTime
355 !------------------------------------------------------------------------------
356 !BOP
357 ! !IROUTINE:  ESMF_AlarmGet - Get an alarm's parameters -- compatibility with ESMF 2.0.1
359 ! !INTERFACE:
360       subroutine ESMF_AlarmGet(alarm, PrevRingTime, RingInterval, rc)
362 ! !ARGUMENTS:
363       type(ESMF_Alarm), intent(in) :: alarm
364       type(ESMF_Time), intent(out), optional :: PrevRingTime
365       type(ESMF_TimeInterval), intent(out), optional :: RingInterval
366       integer, intent(out), optional :: rc
367       integer :: ierr
369 ! !DESCRIPTION:
370 !     Get an {\tt ESMF\_Alarm}'s previous ring time
372 !     The arguments are:
373 !     \begin{description}
374 !     \item[alarm]
375 !          The object instance to get the previous ring time
376 !     \item[PrevRingTime]
377 !          The {\tt ESMF\_Alarm}'s previous ring time
378 !     \item[{[rc]}]
379 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
380 !     \end{description}
382 ! !REQUIREMENTS:
383 !     TMG4.7, TMG4.8
384 !EOP
386       ierr = ESMF_SUCCESS
388       IF ( PRESENT(PrevRingTime) ) THEN
389         CALL ESMF_AlarmGetPrevRingTime(alarm, PrevRingTime, rc=ierr)
390       ENDIF
391       IF ( PRESENT(RingInterval) ) THEN
392         CALL ESMF_AlarmGetRingInterval(alarm, RingInterval, rc=ierr)
393       ENDIF
395       IF ( PRESENT(rc) ) THEN
396         rc = ierr
397       ENDIF
399       end subroutine ESMF_AlarmGet
401 !------------------------------------------------------------------------------
402 !BOP
403 ! !IROUTINE:  ESMF_AlarmGetPrevRingTime - Get an alarm's previous ring time
405 ! !INTERFACE:
406       subroutine ESMF_AlarmGetPrevRingTime(alarm, PrevRingTime, rc)
408 ! !ARGUMENTS:
409       type(ESMF_Alarm), intent(in) :: alarm
410       type(ESMF_Time), intent(out) :: PrevRingTime
411       integer, intent(out), optional :: rc
413 ! !DESCRIPTION:
414 !     Get an {\tt ESMF\_Alarm}'s previous ring time
416 !     The arguments are:
417 !     \begin{description}
418 !     \item[alarm]
419 !          The object instance to get the previous ring time
420 !     \item[PrevRingTime]
421 !          The {\tt ESMF\_Alarm}'s previous ring time
422 !     \item[{[rc]}]
423 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
424 !     \end{description}
426 ! !REQUIREMENTS:
427 !     TMG4.7, TMG4.8
428 !EOP
429       IF ( ASSOCIATED( alarm%alarmint ) ) THEN
430         PrevRingTime = alarm%alarmint%PrevRingTime
431         IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
432       ELSE
433         IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
434       ENDIF
435       end subroutine ESMF_AlarmGetPrevRingTime
437 !------------------------------------------------------------------------------
438 !BOP
439 ! !IROUTINE:  ESMF_AlarmSetPrevRingTime - Set an alarm's previous ring time
441 ! !INTERFACE:
442       subroutine ESMF_AlarmSetPrevRingTime(alarm, PrevRingTime, rc)
444 ! !ARGUMENTS:
445       type(ESMF_Alarm), intent(out) :: alarm
446       type(ESMF_Time), intent(in) :: PrevRingTime
447       integer, intent(out), optional :: rc
448    
449 ! !DESCRIPTION:
450 !     Set an {\tt ESMF\_Alarm}'s previous ring time
452 !     The arguments are:
453 !     \begin{description}
454 !     \item[alarm]
455 !          The object instance to set the previous ring time
456 !     \item[PrevRingTime]
457 !          The {\tt ESMF\_Alarm}'s previous ring time to set
458 !     \item[{[rc]}]
459 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
460 !     \end{description}
462 ! !REQUIREMENTS:
463 !     TMG4.7, TMG4.8
464 !EOP
465       CALL wrf_error_fatal( 'ESMF_AlarmSetPrevRingTime not supported' )
466       end subroutine ESMF_AlarmSetPrevRingTime
468 !------------------------------------------------------------------------------
469 !BOP
470 ! !IROUTINE:  ESMF_AlarmGetStopTime - Get an alarm's stop time
472 ! !INTERFACE:
473       subroutine ESMF_AlarmGetStopTime(alarm, StopTime, rc)
475 ! !ARGUMENTS:
476       type(ESMF_Alarm), intent(in) :: alarm
477       type(ESMF_Time), intent(out) :: StopTime
478       integer, intent(out), optional :: rc
480 ! !DESCRIPTION:
481 !     Get an {\tt ESMF\_Alarm}'s stop time
483 !     The arguments are:
484 !     \begin{description}
485 !     \item[alarm]
486 !          The object instance to get the stop time
487 !     \item[StopTime]
488 !          The {\tt ESMF\_Alarm}'s stop time
489 !     \item[{[rc]}]
490 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
491 !     \end{description}
493 ! !REQUIREMENTS:
494 !     TMG4.5.2, TMG4.7
495 !EOP
496       CALL wrf_error_fatal( 'ESMF_AlarmGetStopTime not supported' )
497       end subroutine ESMF_AlarmGetStopTime
499 !------------------------------------------------------------------------------
500 !BOP
501 ! !IROUTINE:  ESMF_AlarmSetStopTime - Set an alarm's stop time
503 ! !INTERFACE:
504       subroutine ESMF_AlarmSetStopTime(alarm, StopTime, rc)
506 ! !ARGUMENTS:
507       type(ESMF_Alarm), intent(out) :: alarm
508       type(ESMF_Time), intent(in) :: StopTime
509       integer, intent(out), optional :: rc
511 ! !DESCRIPTION:
512 !     Set an {\tt ESMF\_Alarm}'s stop time
514 !     The arguments are:
515 !     \begin{description}
516 !     \item[alarm]
517 !          The object instance to set the stop time
518 !     \item[StopTime]
519 !          The {\tt ESMF\_Alarm}'s stop time
520 !     \item[{[rc]}]
521 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
522 !     \end{description}
524 ! !REQUIREMENTS:
525 !     TMG4.5.2, TMG4.7
526 !EOP
527       CALL wrf_error_fatal( 'ESMF_AlarmSetStopTime not supported' )
528       end subroutine ESMF_AlarmSetStopTime
530 !------------------------------------------------------------------------------
531 !BOP
532 ! !IROUTINE: ESMF_AlarmEnable - Enables an alarm
534 ! !INTERFACE:
535       subroutine ESMF_AlarmEnable(alarm, rc)
537 ! !ARGUMENTS:
538       type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
539       integer, intent(out), optional :: rc
541 ! !DESCRIPTION:
542 !     Enables an {\tt ESMF\_Alarm} to function
544 !     The arguments are:
545 !     \begin{description}
546 !     \item[alarm]
547 !          The object instance to enable
548 !     \item[{[rc]}]
549 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
550 !     \end{description}
552 ! !REQUIREMENTS:
553 !     TMG4.5.3
554 !EOP
555       IF ( ASSOCIATED( alarm%alarmint ) ) THEN
556         alarm%alarmint%Enabled = .TRUE.
557         IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
558       ELSE
559         IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
560       ENDIF
561       end subroutine ESMF_AlarmEnable
563 !------------------------------------------------------------------------------
564 !BOP
565 ! !IROUTINE: ESMF_AlarmDisable - Disables an alarm
567 ! !INTERFACE:
568       subroutine ESMF_AlarmDisable(alarm, rc)
570 ! !ARGUMENTS:
571       type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
572       integer, intent(out), optional :: rc
574 ! !DESCRIPTION:
575 !     Disables an {\tt ESMF\_Alarm}
577 !     The arguments are:
578 !     \begin{description}
579 !     \item[alarm]
580 !          The object instance to disable
581 !     \item[{[rc]}]
582 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
583 !     \end{description}
585 ! !REQUIREMENTS:
586 !     TMG4.5.3
587 !EOP
588       IF ( ASSOCIATED( alarm%alarmint ) ) THEN
589         alarm%alarmint%Enabled = .FALSE.
590         IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
591       ELSE
592         IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
593       ENDIF
594       end subroutine ESMF_AlarmDisable
596 !------------------------------------------------------------------------------
597 !BOP
598 ! !IROUTINE:  ESMF_AlarmRingerOn - Turn on an alarm
601 ! !INTERFACE:
602       subroutine ESMF_AlarmRingerOn(alarm, rc)
604 ! !ARGUMENTS:
605       type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
606       integer, intent(out), optional :: rc
607     
608 ! !DESCRIPTION:
609 !     Turn on an {\tt ESMF\_Alarm}; sets ringing state
611 !     The arguments are:
612 !     \begin{description}
613 !     \item[alarm]
614 !          The object instance to turn on
615 !     \item[{[rc]}]
616 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
617 !     \end{description}
619 ! !REQUIREMENTS:
620 !     TMG4.6
621 !EOP
622       IF ( ASSOCIATED( alarm%alarmint ) ) THEN
623         IF ( alarm%alarmint%Enabled ) THEN
624           alarm%alarmint%Ringing = .TRUE.
625           IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
626         ELSE
627           alarm%alarmint%Ringing = .FALSE.
628           IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
629         ENDIF
630       ELSE
631         IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
632       ENDIF
634       end subroutine ESMF_AlarmRingerOn
636 !------------------------------------------------------------------------------
637 !BOP
638 ! !IROUTINE:  ESMF_AlarmRingerOff - Turn off an alarm
640 ! !INTERFACE:
641       subroutine ESMF_AlarmRingerOff(alarm, rc)
643 ! !ARGUMENTS:
644       type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
645       integer, intent(out), optional :: rc
646     
647 ! !DESCRIPTION:
648 !     Turn off an {\tt ESMF\_Alarm}; unsets ringing state
650 !     The arguments are:
651 !     \begin{description}
652 !     \item[alarm]
653 !          The object instance to turn off   
654 !     \item[{[rc]}]
655 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
656 !     \end{description}
658 ! !REQUIREMENTS:
659 !     TMG4.6
660 !EOP
661       IF ( ASSOCIATED( alarm%alarmint ) ) THEN
662         alarm%alarmint%Ringing = .FALSE.
663         IF ( alarm%alarmint%Enabled ) THEN
664           IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
665         ELSE
666           IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
667         ENDIF
668       ELSE
669         IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
670       ENDIF
671       end subroutine ESMF_AlarmRingerOff
673 !------------------------------------------------------------------------------
674 !BOP
675 ! !IROUTINE:  ESMF_AlarmIsRinging - Check if alarm is ringing
677 ! !INTERFACE:
678       function ESMF_AlarmIsRinging(alarm, rc)
680 ! !RETURN VALUE:
681       logical :: ESMF_AlarmIsRinging
683 ! !ARGUMENTS:
684       type(ESMF_Alarm), intent(in) :: alarm
685       integer, intent(out), optional :: rc
687 ! !DESCRIPTION:
688 !     Check if {\tt ESMF\_Alarm} is ringing.
690 !     The arguments are:
691 !     \begin{description}
692 !     \item[alarm]
693 !          The object instance to check for ringing state  
694 !     \item[{[rc]}]
695 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
696 !     \end{description}
698 ! !REQUIREMENTS:
699 !     TMG4.4
700 !EOP
701       IF ( ASSOCIATED( alarm%alarmint ) ) THEN
702         IF ( alarm%alarmint%Enabled ) THEN
703           ESMF_AlarmIsRinging = alarm%alarmint%Ringing
704           IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
705         ELSE
706           ESMF_AlarmIsRinging = .FALSE.
707           IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
708         ENDIF
709       ELSE
710         IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
711       ENDIF
712       end function ESMF_AlarmIsRinging
714 !------------------------------------------------------------------------------
715 !BOP
716 ! !IROUTINE: ESMF_AlarmCheckRingTime - Method used by a clock to check whether to trigger an alarm
718 ! !INTERFACE:
719       function ESMF_AlarmCheckRingTime(alarm, ClockCurrTime, positive, rc)
721 ! !RETURN VALUE:
722       logical :: ESMF_AlarmCheckRingTime
724 ! !ARGUMENTS:
725       type(ESMF_Alarm), intent(inout) :: alarm
726       type(ESMF_Time), intent(in) :: ClockCurrTime
727       integer, intent(in) :: positive
728       integer, intent(out), optional :: rc
730 ! !DESCRIPTION:
731 !     Main method used by a {\tt ESMF\_Clock} to check whether to trigger
732 !     the {\tt ESMF\_Alarm} 
734 !     The arguments are:
735 !     \begin{description}
736 !     \item[alarm]
737 !          The object instance to check if time to ring   
738 !     \item[ClockCurrTime]
739 !          The {\tt ESMF\_Clock}'s current time
740 !     \item[positive]
741 !          Whether to check ring time in the positive or negative direction
742 !     \item[{[rc]}]
743 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
744 !     \end{description}
746 ! !REQUIREMENTS:
747 !     TMG4.4, TMG4.6
748 !EOP
749       CALL wrf_error_fatal( 'ESMF_AlarmCheckRingTime not supported' )
750       ESMF_AlarmCheckRingTime = .FALSE.  ! keep compilers happy
751       end function ESMF_AlarmCheckRingTime
753 !------------------------------------------------------------------------------
754 !BOP
755 ! !IROUTINE:  ESMF_AlarmEQ - Compare two alarms for equality
757 ! !INTERFACE:
758       function ESMF_AlarmEQ(alarm1, alarm2)
760 ! !RETURN VALUE:
761       logical :: ESMF_AlarmEQ
763 ! !ARGUMENTS:
764       type(ESMF_Alarm), intent(in) :: alarm1
765       type(ESMF_Alarm), intent(in) :: alarm2
767 ! !DESCRIPTION:
768 !     Compare two alarms for equality; return true if equal, false otherwise
769 !     Maps to overloaded (==) operator interface function
771 !     The arguments are:
772 !     \begin{description}
773 !     \item[alarm1]
774 !          The first {\tt ESMF\_Alarm} to compare
775 !     \item[alarm2]
776 !          The second {\tt ESMF\_Alarm} to compare
777 !     \end{description}
779 ! !REQUIREMENTS:  
780 !EOP
781       CALL wrf_error_fatal( 'ESMF_AlarmEQ not supported ' )
782       ESMF_AlarmEQ = .FALSE.       ! keep compilers happy
783       end function ESMF_AlarmEQ
785 !------------------------------------------------------------------------------
787 ! This section defines the overridden Read, Write, Validate and Print methods
788 ! from the ESMF_Base class
790 !------------------------------------------------------------------------------
791 !BOP
792 ! !IROUTINE: ESMF_AlarmRead - restores an alarm
794 ! !INTERFACE:
795       subroutine ESMF_AlarmRead(alarm, RingInterval, RingTime, &
796                            PrevRingTime, StopTime, Ringing, &
797                            Enabled, ID, rc)
799 ! !ARGUMENTS:
800       type(ESMF_Alarm), intent(out) :: alarm
801       type(ESMF_TimeInterval), intent(in) :: RingInterval
802       type(ESMF_Time), intent(in) :: RingTime
803       type(ESMF_Time), intent(in) :: PrevRingTime
804       type(ESMF_Time), intent(in) :: StopTime
805       logical, intent(in) :: Ringing
806       logical, intent(in) :: Enabled
807       integer, intent(in) :: ID
808       integer, intent(out), optional :: rc
810 ! !DESCRIPTION:
811 !     Restores an {\tt ESMF\_Alarm}
813 !     The arguments are:
814 !     \begin{description}
815 !     \item[alarm]
816 !          The object instance to restore
817 !     \item[RingInterval]
818 !          The ring interval for repeating alarms
819 !     \item[RingTime]
820 !          Ring time for one-shot or first repeating alarm
821 !     \item[PrevRingTime]
822 !          The {\tt ESMF\_Alarm}'s previous ring time
823 !     \item[StopTime]
824 !          Stop time for repeating alarms
825 !     \item[Ringing]
826 !          The {\tt ESMF\_Alarm}'s ringing state
827 !     \item[Enabled]
828 !          {\tt ESMF\_Alarm} enabled/disabled
829 !     \item[ID]
830 !          The {\tt ESMF\_Alarm}'s ID
831 !     \item[{[rc]}]
832 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
833 !     \end{description}
835 ! !REQUIREMENTS:
836 !EOP
837       CALL wrf_error_fatal( 'ESMF_AlarmRead not supported' )
838       end subroutine ESMF_AlarmRead
840 !------------------------------------------------------------------------------
841 !BOP
842 ! !IROUTINE: ESMF_AlarmWrite - saves an alarm
844 ! !INTERFACE:
845       subroutine ESMF_AlarmWrite(alarm, RingInterval, RingTime, &
846                             PrevRingTime, StopTime, Ringing, &
847                             Enabled, ID, rc)
849 ! !ARGUMENTS:
850       type(ESMF_Alarm), intent(in) :: alarm
851       type(ESMF_TimeInterval), intent(out) :: RingInterval
852       type(ESMF_Time), intent(out) :: RingTime
853       type(ESMF_Time), intent(out) :: PrevRingTime
854       type(ESMF_Time), intent(out) :: StopTime
855       logical, intent(out) :: Ringing
856       logical, intent(out) :: Enabled
857       integer, intent(out) :: ID
858       integer, intent(out), optional :: rc
860 ! !DESCRIPTION:
861 !     Saves an {\tt ESMF\_Alarm}
863 !     The arguments are:
864 !     \begin{description}
865 !     \item[alarm]
866 !          The object instance to save
867 !     \item[RingInterval]
868 !          Ring interval for repeating alarms
869 !     \item[RingTime]
870 !          Ring time for one-shot or first repeating alarm
871 !     \item[PrevRingTime]
872 !          The {\tt ESMF\_Alarm}'s previous ring time
873 !     \item[StopTime]
874 !          Stop time for repeating alarms
875 !     \item[Ringing]
876 !          The {\tt ESMF\_Alarm}'s ringing state
877 !     \item[Enabled]
878 !          {\tt ESMF\_Alarm} enabled/disabled
879 !     \item[ID]
880 !          The {\tt ESMF\_Alarm}'s ID
881 !     \item[{[rc]}]
882 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
883 !     \end{description}
885 ! !REQUIREMENTS:
886 !EOP
887       CALL wrf_error_fatal( 'ESMF_AlarmWrite not supported' )
888       end subroutine ESMF_AlarmWrite
890 !------------------------------------------------------------------------------
891 !BOP
892 ! !IROUTINE:  ESMF_AlarmValidate - Validate an Alarm's properties
894 ! !INTERFACE:
895       subroutine ESMF_AlarmValidate(alarm, opts, rc)
897 ! !ARGUMENTS:
898       type(ESMF_Alarm), intent(in) :: alarm
899       character (len=*), intent(in), optional :: opts
900       integer, intent(out), optional :: rc
902 ! !DESCRIPTION:
903 !     Perform a validation check on a {\tt ESMF\_Alarm}'s properties
905 !     The arguments are:  
906 !     \begin{description}
907 !     \item[alarm]
908 !          {\tt ESMF\_Alarm} to validate
909 !     \item[{[opts]}]
910 !          Validate options
911 !     \item[{[rc]}]
912 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
913 !     \end{description} 
915 ! !REQUIREMENTS:
916 !     TMGn.n.n
917 !EOP
918       CALL wrf_error_fatal( 'ESMF_AlarmValidate not supported' )
919       end subroutine ESMF_AlarmValidate
921 !------------------------------------------------------------------------------
922 !BOP
923 ! !IROUTINE:  ESMF_AlarmPrint - Print out an Alarm's properties
925 ! !INTERFACE:
926       subroutine ESMF_AlarmPrint(alarm, opts, rc)
928 ! !ARGUMENTS:
929       type(ESMF_Alarm), intent(in) :: alarm
930       character (len=*), intent(in), optional :: opts
931       integer, intent(out), optional :: rc
933 ! !DESCRIPTION:
934 !     To support testing/debugging, print out a {\tt ESMF\_Alarm}'s
935 !     properties.
937 !     The arguments are:
938 !     \begin{description}
939 !     \item[alarm]
940 !          {\tt ESMF\_Alarm} to print out
941 !     \item[{[opts]}]
942 !          Print options
943 !     \item[{[rc]}]
944 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
945 !     \end{description}
947 ! !REQUIREMENTS:
948 !     TMGn.n.n
949 !EOP
950       CALL wrf_error_fatal( 'ESMF_AlarmPrint not supported' )
951       end subroutine ESMF_AlarmPrint
953 !------------------------------------------------------------------------------
955       end module WRF_ESMF_AlarmMod