source: trunk/WRF.COMMON/WRFV3/external/esmf_time_f90/ESMF_Alarm.F90 @ 2759

Last change on this file since 2759 was 2759, checked in by aslmd, 2 years ago

adding unmodified code from WRFV3.0.1.1, expurged from useless data +1M size

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