source: lmdz_wrf/WRFV3/external/esmf_time_f90/ESMF_Alarm.F90 @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 28.5 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, PrevRingTime, &
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, PrevRingTime
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( PrevRingTime ) ) THEN
198          alarm%alarmint%PrevRingTime = PrevRingTime
199        ENDIF
200        IF ( PRESENT( RingTime ) ) THEN
201          alarm%alarmint%RingTime = RingTime
202          alarm%alarmint%RingTimeSet = .TRUE.
203        ENDIF
204        IF ( PRESENT( StopTime ) ) THEN
205          alarm%alarmint%StopTime = StopTime
206          alarm%alarmint%StopTimeSet = .TRUE.
207        ENDIF
208        alarm%alarmint%Enabled = .TRUE.
209        IF ( PRESENT( Enabled ) ) THEN
210          alarm%alarmint%Enabled = Enabled
211        ENDIF
212        IF ( PRESENT( rc ) ) THEN
213          rc = ESMF_SUCCESS
214        ENDIF
215        alarm%alarmint%Ringing = .FALSE.
216        alarm%alarmint%Enabled = .TRUE.
217      ELSE
218        IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
219      ENDIF
220
221      end subroutine ESMF_AlarmSet
222
223
224
225! Deallocate memory for ESMF_Alarm
226      SUBROUTINE ESMF_AlarmDestroy( alarm, rc )
227         TYPE(ESMF_Alarm), INTENT(INOUT) :: alarm
228         INTEGER,          INTENT(  OUT), OPTIONAL :: rc
229         IF ( ASSOCIATED( alarm%alarmint ) ) THEN
230           DEALLOCATE( alarm%alarmint )
231         ENDIF
232         ! TBH:  ignore deallocate errors, for now
233         IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
234      END SUBROUTINE ESMF_AlarmDestroy
235
236
237
238!------------------------------------------------------------------------------
239!BOP
240! !IROUTINE: ESMF_AlarmGetRingInterval - Get an alarm's ring interval
241!
242! !INTERFACE:
243      subroutine ESMF_AlarmGetRingInterval(alarm, RingInterval, rc)
244
245! !ARGUMENTS:
246      type(ESMF_Alarm), intent(in) :: alarm
247      type(ESMF_TimeInterval), intent(out) :: RingInterval
248      integer, intent(out), optional :: rc
249
250! !DESCRIPTION:
251!     Get an {\tt ESMF\_Alarm}'s ring interval
252!
253!     The arguments are:
254!     \begin{description}
255!     \item[alarm]
256!          The object instance to get the ring interval
257!     \item[RingInterval]
258!          The {\tt Alarm}'s ring interval
259!     \item[{[rc]}]
260!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
261!     \end{description}
262
263! !REQUIREMENTS:
264!     TMG4.7
265!EOP
266      RingInterval = alarm%alarmint%RingInterval
267
268      end subroutine ESMF_AlarmGetRingInterval
269 
270!------------------------------------------------------------------------------
271!BOP
272! !IROUTINE: ESMF_AlarmSetRingInterval - Set an alarm's ring interval
273!
274! !INTERFACE:
275      subroutine ESMF_AlarmSetRingInterval(alarm, RingInterval, rc)
276
277! !ARGUMENTS:
278      type(ESMF_Alarm), intent(out) :: alarm
279      type(ESMF_TimeInterval), intent(in) :: RingInterval
280      integer, intent(out), optional :: rc
281
282! !DESCRIPTION:
283!     Set an {\tt ESMF\_Alarm}'s ring interval
284!
285!     The arguments are:
286!     \begin{description}
287!     \item[alarm]
288!          The object instance to set the ring interval
289!     \item[RingInterval]
290!          The {\tt Alarm}'s ring interval
291!     \item[{[rc]}]
292!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
293!     \end{description}
294!
295! !REQUIREMENTS:
296!     TMG4.5.2, TMG4.7
297!EOP
298      CALL wrf_error_fatal( 'ESMF_AlarmSetRingInterval not supported' )
299      end subroutine ESMF_AlarmSetRingInterval
300
301!------------------------------------------------------------------------------
302!BOP
303! !IROUTINE:  ESMF_AlarmGetRingTime - Get an alarm's time to ring
304!
305! !INTERFACE:
306      subroutine ESMF_AlarmGetRingTime(alarm, RingTime, rc)
307
308! !ARGUMENTS:
309      type(ESMF_Alarm), intent(in) :: alarm
310      type(ESMF_Time), intent(out) :: RingTime
311      integer, intent(out), optional :: rc
312
313! !DESCRIPTION:
314!     Get an {\tt ESMF\_Alarm}'s time to ring
315!
316!     The arguments are:
317!     \begin{description}
318!     \item[alarm]
319!          The object instance to get the ring time
320!     \item[RingTime]
321!          The {\tt ESMF\_Alarm}'s ring time
322!     \item[{[rc]}]
323!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
324!     \end{description}
325!
326! !REQUIREMENTS:
327!     TMG4.7, TMG4.8
328!EOP
329      CALL wrf_error_fatal( 'ESMF_AlarmGetRingTime not supported' )
330      end subroutine ESMF_AlarmGetRingTime
331
332!------------------------------------------------------------------------------
333!BOP
334! !IROUTINE:  ESMF_AlarmSetRingTime - Set an alarm's time to ring
335!
336! !INTERFACE:
337      subroutine ESMF_AlarmSetRingTime(alarm, RingTime, rc)
338
339! !ARGUMENTS:
340      type(ESMF_Alarm), intent(out) :: alarm
341      type(ESMF_Time), intent(in) :: RingTime
342      integer, intent(out), optional :: rc
343
344! !DESCRIPTION:
345!     Set an {\tt ESMF\_Alarm}'s time to ring
346!
347!     The arguments are:
348!     \begin{description}
349!     \item[alarm]
350!          The object instance to set the ring time
351!     \item[RingTime]
352!          The {\tt ESMF\_Alarm}'s ring time to set
353!     \item[{[rc]}]
354!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
355!     \end{description}
356!
357! !REQUIREMENTS:
358!     TMG4.5.1, TMG4.7, TMG4.8
359!EOP
360      CALL wrf_error_fatal( 'ESMF_AlarmSetRingTime not supported' )
361      end subroutine ESMF_AlarmSetRingTime
362
363!------------------------------------------------------------------------------
364!BOP
365! !IROUTINE:  ESMF_AlarmGet - Get an alarm's parameters -- compatibility with ESMF 2.0.1
366!
367! !INTERFACE:
368      subroutine ESMF_AlarmGet(alarm, PrevRingTime, RingInterval, rc)
369
370! !ARGUMENTS:
371      type(ESMF_Alarm), intent(in) :: alarm
372      type(ESMF_Time), intent(out), optional :: PrevRingTime
373      type(ESMF_TimeInterval), intent(out), optional :: RingInterval
374      integer, intent(out), optional :: rc
375      integer :: ierr
376
377! !DESCRIPTION:
378!     Get an {\tt ESMF\_Alarm}'s previous ring time
379!
380!     The arguments are:
381!     \begin{description}
382!     \item[alarm]
383!          The object instance to get the previous ring time
384!     \item[PrevRingTime]
385!          The {\tt ESMF\_Alarm}'s previous ring time
386!     \item[{[rc]}]
387!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
388!     \end{description}
389!
390! !REQUIREMENTS:
391!     TMG4.7, TMG4.8
392!EOP
393
394      ierr = ESMF_SUCCESS
395
396      IF ( PRESENT(PrevRingTime) ) THEN
397        CALL ESMF_AlarmGetPrevRingTime(alarm, PrevRingTime, rc=ierr)
398      ENDIF
399      IF ( PRESENT(RingInterval) ) THEN
400        CALL ESMF_AlarmGetRingInterval(alarm, RingInterval, rc=ierr)
401      ENDIF
402
403      IF ( PRESENT(rc) ) THEN
404        rc = ierr
405      ENDIF
406
407      end subroutine ESMF_AlarmGet
408
409!------------------------------------------------------------------------------
410!BOP
411! !IROUTINE:  ESMF_AlarmGetPrevRingTime - Get an alarm's previous ring time
412!
413! !INTERFACE:
414      subroutine ESMF_AlarmGetPrevRingTime(alarm, PrevRingTime, rc)
415
416! !ARGUMENTS:
417      type(ESMF_Alarm), intent(in) :: alarm
418      type(ESMF_Time), intent(out) :: PrevRingTime
419      integer, intent(out), optional :: rc
420
421! !DESCRIPTION:
422!     Get an {\tt ESMF\_Alarm}'s previous ring time
423!
424!     The arguments are:
425!     \begin{description}
426!     \item[alarm]
427!          The object instance to get the previous ring time
428!     \item[PrevRingTime]
429!          The {\tt ESMF\_Alarm}'s previous ring time
430!     \item[{[rc]}]
431!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
432!     \end{description}
433!
434! !REQUIREMENTS:
435!     TMG4.7, TMG4.8
436!EOP
437      IF ( ASSOCIATED( alarm%alarmint ) ) THEN
438        PrevRingTime = alarm%alarmint%PrevRingTime
439        IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
440      ELSE
441        IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
442      ENDIF
443      end subroutine ESMF_AlarmGetPrevRingTime
444
445!------------------------------------------------------------------------------
446!BOP
447! !IROUTINE:  ESMF_AlarmSetPrevRingTime - Set an alarm's previous ring time
448!
449! !INTERFACE:
450      subroutine ESMF_AlarmSetPrevRingTime(alarm, PrevRingTime, rc)
451
452! !ARGUMENTS:
453      type(ESMF_Alarm), intent(out) :: alarm
454      type(ESMF_Time), intent(in) :: PrevRingTime
455      integer, intent(out), optional :: rc
456   
457! !DESCRIPTION:
458!     Set an {\tt ESMF\_Alarm}'s previous ring time
459!
460!     The arguments are:
461!     \begin{description}
462!     \item[alarm]
463!          The object instance to set the previous ring time
464!     \item[PrevRingTime]
465!          The {\tt ESMF\_Alarm}'s previous ring time to set
466!     \item[{[rc]}]
467!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
468!     \end{description}
469!
470! !REQUIREMENTS:
471!     TMG4.7, TMG4.8
472!EOP
473      CALL wrf_error_fatal( 'ESMF_AlarmSetPrevRingTime not supported' )
474      end subroutine ESMF_AlarmSetPrevRingTime
475
476!------------------------------------------------------------------------------
477!BOP
478! !IROUTINE:  ESMF_AlarmGetStopTime - Get an alarm's stop time
479!
480! !INTERFACE:
481      subroutine ESMF_AlarmGetStopTime(alarm, StopTime, rc)
482
483! !ARGUMENTS:
484      type(ESMF_Alarm), intent(in) :: alarm
485      type(ESMF_Time), intent(out) :: StopTime
486      integer, intent(out), optional :: rc
487
488! !DESCRIPTION:
489!     Get an {\tt ESMF\_Alarm}'s stop time
490!
491!     The arguments are:
492!     \begin{description}
493!     \item[alarm]
494!          The object instance to get the stop time
495!     \item[StopTime]
496!          The {\tt ESMF\_Alarm}'s stop time
497!     \item[{[rc]}]
498!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
499!     \end{description}
500!
501! !REQUIREMENTS:
502!     TMG4.5.2, TMG4.7
503!EOP
504      CALL wrf_error_fatal( 'ESMF_AlarmGetStopTime not supported' )
505      end subroutine ESMF_AlarmGetStopTime
506
507!------------------------------------------------------------------------------
508!BOP
509! !IROUTINE:  ESMF_AlarmSetStopTime - Set an alarm's stop time
510!
511! !INTERFACE:
512      subroutine ESMF_AlarmSetStopTime(alarm, StopTime, rc)
513
514! !ARGUMENTS:
515      type(ESMF_Alarm), intent(out) :: alarm
516      type(ESMF_Time), intent(in) :: StopTime
517      integer, intent(out), optional :: rc
518
519! !DESCRIPTION:
520!     Set an {\tt ESMF\_Alarm}'s stop time
521!
522!     The arguments are:
523!     \begin{description}
524!     \item[alarm]
525!          The object instance to set the stop time
526!     \item[StopTime]
527!          The {\tt ESMF\_Alarm}'s stop time
528!     \item[{[rc]}]
529!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
530!     \end{description}
531!
532! !REQUIREMENTS:
533!     TMG4.5.2, TMG4.7
534!EOP
535      CALL wrf_error_fatal( 'ESMF_AlarmSetStopTime not supported' )
536      end subroutine ESMF_AlarmSetStopTime
537
538!------------------------------------------------------------------------------
539!BOP
540! !IROUTINE: ESMF_AlarmEnable - Enables an alarm
541
542! !INTERFACE:
543      subroutine ESMF_AlarmEnable(alarm, rc)
544
545! !ARGUMENTS:
546      type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
547      integer, intent(out), optional :: rc
548
549! !DESCRIPTION:
550!     Enables an {\tt ESMF\_Alarm} to function
551!
552!     The arguments are:
553!     \begin{description}
554!     \item[alarm]
555!          The object instance to enable
556!     \item[{[rc]}]
557!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
558!     \end{description}
559
560! !REQUIREMENTS:
561!     TMG4.5.3
562!EOP
563      IF ( ASSOCIATED( alarm%alarmint ) ) THEN
564        alarm%alarmint%Enabled = .TRUE.
565        IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
566      ELSE
567        IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
568      ENDIF
569      end subroutine ESMF_AlarmEnable
570
571!------------------------------------------------------------------------------
572!BOP
573! !IROUTINE: ESMF_AlarmDisable - Disables an alarm
574
575! !INTERFACE:
576      subroutine ESMF_AlarmDisable(alarm, rc)
577
578! !ARGUMENTS:
579      type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
580      integer, intent(out), optional :: rc
581
582! !DESCRIPTION:
583!     Disables an {\tt ESMF\_Alarm}
584!
585!     The arguments are:
586!     \begin{description}
587!     \item[alarm]
588!          The object instance to disable
589!     \item[{[rc]}]
590!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
591!     \end{description}
592
593! !REQUIREMENTS:
594!     TMG4.5.3
595!EOP
596      IF ( ASSOCIATED( alarm%alarmint ) ) THEN
597        alarm%alarmint%Enabled = .FALSE.
598        IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
599      ELSE
600        IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
601      ENDIF
602      end subroutine ESMF_AlarmDisable
603
604!------------------------------------------------------------------------------
605!BOP
606! !IROUTINE:  ESMF_AlarmRingerOn - Turn on an alarm
607
608
609! !INTERFACE:
610      subroutine ESMF_AlarmRingerOn(alarm, rc)
611
612! !ARGUMENTS:
613      type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
614      integer, intent(out), optional :: rc
615   
616! !DESCRIPTION:
617!     Turn on an {\tt ESMF\_Alarm}; sets ringing state
618!
619!     The arguments are:
620!     \begin{description}
621!     \item[alarm]
622!          The object instance to turn on
623!     \item[{[rc]}]
624!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
625!     \end{description}
626!
627! !REQUIREMENTS:
628!     TMG4.6
629!EOP
630      IF ( ASSOCIATED( alarm%alarmint ) ) THEN
631        IF ( alarm%alarmint%Enabled ) THEN
632          alarm%alarmint%Ringing = .TRUE.
633          IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
634        ELSE
635          alarm%alarmint%Ringing = .FALSE.
636          IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
637        ENDIF
638      ELSE
639        IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
640      ENDIF
641
642      end subroutine ESMF_AlarmRingerOn
643
644!------------------------------------------------------------------------------
645!BOP
646! !IROUTINE:  ESMF_AlarmRingerOff - Turn off an alarm
647
648! !INTERFACE:
649      subroutine ESMF_AlarmRingerOff(alarm, rc)
650
651! !ARGUMENTS:
652      type(ESMF_Alarm), intent(inout) :: alarm  ! really INTENT(OUT)
653      integer, intent(out), optional :: rc
654   
655! !DESCRIPTION:
656!     Turn off an {\tt ESMF\_Alarm}; unsets ringing state
657!
658!     The arguments are:
659!     \begin{description}
660!     \item[alarm]
661!          The object instance to turn off   
662!     \item[{[rc]}]
663!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
664!     \end{description}
665
666! !REQUIREMENTS:
667!     TMG4.6
668!EOP
669      IF ( ASSOCIATED( alarm%alarmint ) ) THEN
670        alarm%alarmint%Ringing = .FALSE.
671        IF ( alarm%alarmint%Enabled ) THEN
672          IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
673        ELSE
674          IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
675        ENDIF
676      ELSE
677        IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
678      ENDIF
679      end subroutine ESMF_AlarmRingerOff
680
681!------------------------------------------------------------------------------
682!BOP
683! !IROUTINE:  ESMF_AlarmIsRinging - Check if alarm is ringing
684
685! !INTERFACE:
686      function ESMF_AlarmIsRinging(alarm, rc)
687!
688! !RETURN VALUE:
689      logical :: ESMF_AlarmIsRinging
690
691! !ARGUMENTS:
692      type(ESMF_Alarm), intent(in) :: alarm
693      integer, intent(out), optional :: rc
694
695! !DESCRIPTION:
696!     Check if {\tt ESMF\_Alarm} is ringing.
697!
698!     The arguments are:
699!     \begin{description}
700!     \item[alarm]
701!          The object instance to check for ringing state 
702!     \item[{[rc]}]
703!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
704!     \end{description}
705
706! !REQUIREMENTS:
707!     TMG4.4
708!EOP
709      IF ( ASSOCIATED( alarm%alarmint ) ) THEN
710        IF ( alarm%alarmint%Enabled ) THEN
711          ESMF_AlarmIsRinging = alarm%alarmint%Ringing
712          IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
713        ELSE
714          ESMF_AlarmIsRinging = .FALSE.
715          IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
716        ENDIF
717      ELSE
718        IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
719      ENDIF
720      end function ESMF_AlarmIsRinging
721
722!------------------------------------------------------------------------------
723!BOP
724! !IROUTINE: ESMF_AlarmCheckRingTime - Method used by a clock to check whether to trigger an alarm
725!
726! !INTERFACE:
727      function ESMF_AlarmCheckRingTime(alarm, ClockCurrTime, positive, rc)
728!
729! !RETURN VALUE:
730      logical :: ESMF_AlarmCheckRingTime
731!
732! !ARGUMENTS:
733      type(ESMF_Alarm), intent(inout) :: alarm
734      type(ESMF_Time), intent(in) :: ClockCurrTime
735      integer, intent(in) :: positive
736      integer, intent(out), optional :: rc
737!
738! !DESCRIPTION:
739!     Main method used by a {\tt ESMF\_Clock} to check whether to trigger
740!     the {\tt ESMF\_Alarm}
741!
742!     The arguments are:
743!     \begin{description}
744!     \item[alarm]
745!          The object instance to check if time to ring   
746!     \item[ClockCurrTime]
747!          The {\tt ESMF\_Clock}'s current time
748!     \item[positive]
749!          Whether to check ring time in the positive or negative direction
750!     \item[{[rc]}]
751!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
752!     \end{description}
753
754! !REQUIREMENTS:
755!     TMG4.4, TMG4.6
756!EOP
757      CALL wrf_error_fatal( 'ESMF_AlarmCheckRingTime not supported' )
758      ESMF_AlarmCheckRingTime = .FALSE.  ! keep compilers happy
759      end function ESMF_AlarmCheckRingTime
760
761!------------------------------------------------------------------------------
762!BOP
763! !IROUTINE:  ESMF_AlarmEQ - Compare two alarms for equality
764!
765! !INTERFACE:
766      function ESMF_AlarmEQ(alarm1, alarm2)
767!
768! !RETURN VALUE:
769      logical :: ESMF_AlarmEQ
770
771! !ARGUMENTS:
772      type(ESMF_Alarm), intent(in) :: alarm1
773      type(ESMF_Alarm), intent(in) :: alarm2
774
775! !DESCRIPTION:
776!     Compare two alarms for equality; return true if equal, false otherwise
777!     Maps to overloaded (==) operator interface function
778!
779!     The arguments are:
780!     \begin{description}
781!     \item[alarm1]
782!          The first {\tt ESMF\_Alarm} to compare
783!     \item[alarm2]
784!          The second {\tt ESMF\_Alarm} to compare
785!     \end{description}
786!
787! !REQUIREMENTS: 
788!EOP
789      CALL wrf_error_fatal( 'ESMF_AlarmEQ not supported ' )
790      ESMF_AlarmEQ = .FALSE.       ! keep compilers happy
791      end function ESMF_AlarmEQ
792
793!------------------------------------------------------------------------------
794!
795! This section defines the overridden Read, Write, Validate and Print methods
796! from the ESMF_Base class
797!
798!------------------------------------------------------------------------------
799!BOP
800! !IROUTINE: ESMF_AlarmRead - restores an alarm
801
802! !INTERFACE:
803      subroutine ESMF_AlarmRead(alarm, RingInterval, RingTime, &
804                           PrevRingTime, StopTime, Ringing, &
805                           Enabled, ID, rc)
806
807! !ARGUMENTS:
808      type(ESMF_Alarm), intent(out) :: alarm
809      type(ESMF_TimeInterval), intent(in) :: RingInterval
810      type(ESMF_Time), intent(in) :: RingTime
811      type(ESMF_Time), intent(in) :: PrevRingTime
812      type(ESMF_Time), intent(in) :: StopTime
813      logical, intent(in) :: Ringing
814      logical, intent(in) :: Enabled
815      integer, intent(in) :: ID
816      integer, intent(out), optional :: rc
817
818! !DESCRIPTION:
819!     Restores an {\tt ESMF\_Alarm}
820!
821!     The arguments are:
822!     \begin{description}
823!     \item[alarm]
824!          The object instance to restore
825!     \item[RingInterval]
826!          The ring interval for repeating alarms
827!     \item[RingTime]
828!          Ring time for one-shot or first repeating alarm
829!     \item[PrevRingTime]
830!          The {\tt ESMF\_Alarm}'s previous ring time
831!     \item[StopTime]
832!          Stop time for repeating alarms
833!     \item[Ringing]
834!          The {\tt ESMF\_Alarm}'s ringing state
835!     \item[Enabled]
836!          {\tt ESMF\_Alarm} enabled/disabled
837!     \item[ID]
838!          The {\tt ESMF\_Alarm}'s ID
839!     \item[{[rc]}]
840!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
841!     \end{description}
842!
843! !REQUIREMENTS:
844!EOP
845      CALL wrf_error_fatal( 'ESMF_AlarmRead not supported' )
846      end subroutine ESMF_AlarmRead
847
848!------------------------------------------------------------------------------
849!BOP
850! !IROUTINE: ESMF_AlarmWrite - saves an alarm
851
852! !INTERFACE:
853      subroutine ESMF_AlarmWrite(alarm, RingInterval, RingTime, &
854                            PrevRingTime, StopTime, Ringing, &
855                            Enabled, ID, rc)
856
857! !ARGUMENTS:
858      type(ESMF_Alarm), intent(in) :: alarm
859      type(ESMF_TimeInterval), intent(out) :: RingInterval
860      type(ESMF_Time), intent(out) :: RingTime
861      type(ESMF_Time), intent(out) :: PrevRingTime
862      type(ESMF_Time), intent(out) :: StopTime
863      logical, intent(out) :: Ringing
864      logical, intent(out) :: Enabled
865      integer, intent(out) :: ID
866      integer, intent(out), optional :: rc
867
868! !DESCRIPTION:
869!     Saves an {\tt ESMF\_Alarm}
870!
871!     The arguments are:
872!     \begin{description}
873!     \item[alarm]
874!          The object instance to save
875!     \item[RingInterval]
876!          Ring interval for repeating alarms
877!     \item[RingTime]
878!          Ring time for one-shot or first repeating alarm
879!     \item[PrevRingTime]
880!          The {\tt ESMF\_Alarm}'s previous ring time
881!     \item[StopTime]
882!          Stop time for repeating alarms
883!     \item[Ringing]
884!          The {\tt ESMF\_Alarm}'s ringing state
885!     \item[Enabled]
886!          {\tt ESMF\_Alarm} enabled/disabled
887!     \item[ID]
888!          The {\tt ESMF\_Alarm}'s ID
889!     \item[{[rc]}]
890!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
891!     \end{description}
892!
893! !REQUIREMENTS:
894!EOP
895      CALL wrf_error_fatal( 'ESMF_AlarmWrite not supported' )
896      end subroutine ESMF_AlarmWrite
897
898!------------------------------------------------------------------------------
899!BOP
900! !IROUTINE:  ESMF_AlarmValidate - Validate an Alarm's properties
901
902! !INTERFACE:
903      subroutine ESMF_AlarmValidate(alarm, opts, rc)
904
905! !ARGUMENTS:
906      type(ESMF_Alarm), intent(in) :: alarm
907      character (len=*), intent(in), optional :: opts
908      integer, intent(out), optional :: rc
909
910! !DESCRIPTION:
911!     Perform a validation check on a {\tt ESMF\_Alarm}'s properties
912!
913!     The arguments are: 
914!     \begin{description}
915!     \item[alarm]
916!          {\tt ESMF\_Alarm} to validate
917!     \item[{[opts]}]
918!          Validate options
919!     \item[{[rc]}]
920!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
921!     \end{description}
922!
923! !REQUIREMENTS:
924!     TMGn.n.n
925!EOP
926      CALL wrf_error_fatal( 'ESMF_AlarmValidate not supported' )
927      end subroutine ESMF_AlarmValidate
928
929!------------------------------------------------------------------------------
930!BOP
931! !IROUTINE:  ESMF_AlarmPrint - Print out an Alarm's properties
932
933! !INTERFACE:
934      subroutine ESMF_AlarmPrint(alarm, opts, rc)
935
936! !ARGUMENTS:
937      type(ESMF_Alarm), intent(in) :: alarm
938      character (len=*), intent(in), optional :: opts
939      integer, intent(out), optional :: rc
940
941! !DESCRIPTION:
942!     To support testing/debugging, print out a {\tt ESMF\_Alarm}'s
943!     properties.
944!
945!     The arguments are:
946!     \begin{description}
947!     \item[alarm]
948!          {\tt ESMF\_Alarm} to print out
949!     \item[{[opts]}]
950!          Print options
951!     \item[{[rc]}]
952!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
953!     \end{description}
954!
955! !REQUIREMENTS:
956!     TMGn.n.n
957!EOP
958      CALL wrf_error_fatal( 'ESMF_AlarmPrint not supported' )
959      end subroutine ESMF_AlarmPrint
960
961!------------------------------------------------------------------------------
962
963      end module ESMF_AlarmMod
Note: See TracBrowser for help on using the repository browser.