source: trunk/WRF.COMMON/WRFV3/external/esmf_time_f90/ESMF_Clock.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: 45.0 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 Clock Module
13      module ESMF_ClockMod
14!     
15!==============================================================================
16!     
17! This file contains the Clock class definition and all Clock class methods.
18!     
19!------------------------------------------------------------------------------
20! INCLUDES
21#include <ESMF_TimeMgr.inc>
22
23!==============================================================================
24!BOPI
25! !MODULE: ESMF_ClockMod
26!     
27! !DESCRIPTION:
28! Part of Time Manager F90 API wrapper of C++ implemenation
29!
30! Defines F90 wrapper entry points for corresponding
31! C++ class {\tt ESMC\_Time} implementation
32!     
33! See {\tt ../include/ESMC\_Clock.h} for complete description
34!
35!------------------------------------------------------------------------------
36! !USES:
37      ! inherit from ESMF base class
38      use ESMF_BaseMod
39
40      ! associated derived types
41      use ESMF_TimeIntervalMod   ! , only : ESMF_TimeInterval, &
42                                 !          ESMF_TimeIntervalIsPositive
43      use ESMF_TimeMod           ! , only : ESMF_Time
44      use ESMF_AlarmMod,        only : ESMF_Alarm
45
46      implicit none
47!
48!------------------------------------------------------------------------------
49! !PRIVATE TYPES:
50      private
51!------------------------------------------------------------------------------
52!     ! ESMF_Clock
53!     
54!     ! F90 class type to match C++ Clock class in size only;
55!     !  all dereferencing within class is performed by C++ implementation
56
57! internals for ESMF_Clock
58      type ESMF_ClockInt
59        type(ESMF_TimeInterval) :: TimeStep
60        type(ESMF_Time)  :: StartTime
61        type(ESMF_Time)  :: StopTime
62        type(ESMF_Time)  :: RefTime
63        type(ESMF_Time)  :: CurrTime
64        type(ESMF_Time)  :: PrevTime
65        integer(ESMF_KIND_I8) :: AdvanceCount
66        integer :: ClockMutex
67        integer :: NumAlarms
68        ! Note:  to mimic ESMF 2.1.0+, AlarmList is maintained
69        ! within ESMF_Clock even though copies of each alarm are
70        ! returned from ESMF_AlarmCreate() at the same time they
71        ! are copied into the AlarmList!  This duplication is not
72        ! as hideous as it might be because the ESMF_Alarm type
73        ! has data members that are all POINTERs (thus the horrible
74        ! shallow-copy-masquerading-as-reference-copy hack works). 
75        type(ESMF_Alarm), pointer, dimension(:) :: AlarmList
76      end type
77
78! Actual public type:  this bit allows easy mimic of "deep" ESMF_ClockCreate
79! in ESMF 2.1.0+
80! NOTE:  DO NOT ADD NON-POINTER STATE TO THIS DATA TYPE.  It emulates ESMF
81!        shallow-copy-masquerading-as-reference-copy. 
82      type ESMF_Clock
83        type(ESMF_ClockInt), pointer  :: clockint
84      end type
85
86!------------------------------------------------------------------------------
87! !PUBLIC TYPES:
88      public ESMF_Clock
89      public ESMF_ClockInt   ! needed on AIX but not PGI
90!------------------------------------------------------------------------------
91!
92! !PUBLIC MEMBER FUNCTIONS:
93      public ESMF_ClockCreate
94      public ESMF_ClockDestroy
95      public ESMF_ClockSet
96!      public ESMF_ClockSetOLD
97      public ESMF_ClockGet
98!      public ESMF_ClockGetAdvanceCount
99!      public ESMF_ClockGetTimeStep
100!      public ESMF_ClockSetTimeStep
101!      public ESMF_ClockGetCurrTime
102!      public ESMF_ClockSetCurrTime
103!      public ESMF_ClockGetStartTime
104!      public ESMF_ClockGetStopTime
105!      public ESMF_ClockGetRefTime
106!      public ESMF_ClockGetPrevTime
107!      public ESMF_ClockGetCurrSimTime
108!      public ESMF_ClockGetPrevSimTime
109! This must be public for ESMF_AlarmClockMod... 
110      public ESMF_ClockAddAlarm
111      public ESMF_ClockGetAlarmList
112!      public ESMF_ClockGetNumAlarms
113!      public ESMF_ClockSyncToWallClock
114      public ESMF_ClockAdvance
115      public ESMF_ClockIsStopTime
116      public ESMF_ClockStopTimeDisable
117
118! Required inherited and overridden ESMF_Base class methods
119
120!      public ESMF_ClockRead
121!      public ESMF_ClockWrite
122      public ESMF_ClockValidate
123      public ESMF_ClockPrint
124!EOPI
125
126!==============================================================================
127
128      contains
129
130!==============================================================================
131!
132! This section includes the Set methods.
133!
134!------------------------------------------------------------------------------
135!BOP
136! !IROUTINE: ESMF_ClockSetOLD - Initialize a clockint
137
138! !INTERFACE:
139      subroutine ESMF_ClockSetOLD(clockint, TimeStep, StartTime, &
140                                  StopTime, RefTime, rc)
141
142! !ARGUMENTS:
143      type(ESMF_ClockInt), intent(out) :: clockint
144      type(ESMF_TimeInterval), intent(in), optional :: TimeStep
145      type(ESMF_Time), intent(in) :: StartTime
146      type(ESMF_Time), intent(in) :: StopTime
147      type(ESMF_Time), intent(in), optional :: RefTime
148      integer, intent(out), optional :: rc
149! Local
150      integer i
151   
152! !DESCRIPTION:
153!     Initialize an {\tt ESMF\_Clock}
154!     
155!     The arguments are:
156!     \begin{description}
157!     \item[clockint]
158!          The object instance to initialize
159!     \item[{[TimeStep]}]
160!          The {\tt ESMF\_Clock}'s time step interval
161!     \item[StartTime]
162!          The {\tt ESMF\_Clock}'s starting time
163!     \item[StopTime]
164!          The {\tt ESMF\_Clock}'s stopping time
165!     \item[{[RefTime]}]
166!          The {\tt ESMF\_Clock}'s reference time
167!     \item[{[rc]}]
168!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
169!     \end{description}
170!     
171! !REQUIREMENTS:
172!     TMG3.1, TMG3.4.4
173!EOP
174      IF ( PRESENT(TimeStep) ) clockint%TimeStep = TimeStep
175      IF ( PRESENT(RefTime) )THEN
176         clockint%RefTime = RefTime
177      ELSE
178         clockint%RefTime = StartTime
179      END IF
180      clockint%CurrTime = StartTime
181      clockint%StartTime = StartTime
182      clockint%StopTime = StopTime
183      clockint%NumAlarms = 0
184      clockint%AdvanceCount = 0
185      ALLOCATE(clockint%AlarmList(MAX_ALARMS))
186      ! TBH:  This incredible hack can be removed once ESMF_*Validate()
187      ! TBH:  can tell if a deep ESMF_* was created or not. 
188      DO i = 1, MAX_ALARMS
189        NULLIFY( clockint%AlarmList( i )%alarmint )
190      ENDDO
191      IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
192   
193      end subroutine ESMF_ClockSetOLD
194
195
196! !IROUTINE: ESMF_ClockSet - Set clock properties -- for compatibility with ESMF 2.0.1
197
198! !INTERFACE:
199      subroutine ESMF_ClockSet(clock, TimeStep, StartTime, StopTime, &
200                               RefTime, CurrTime, rc)
201
202! !ARGUMENTS:
203      type(ESMF_Clock), intent(inout) :: clock
204      type(ESMF_TimeInterval), intent(in), optional :: TimeStep
205      type(ESMF_Time), intent(in), optional :: StartTime
206      type(ESMF_Time), intent(in), optional :: StopTime
207      type(ESMF_Time), intent(in), optional :: RefTime
208      type(ESMF_Time), intent(in), optional :: CurrTime
209      integer, intent(out), optional :: rc
210! Local
211      integer ierr
212   
213! !DESCRIPTION:
214!     Initialize an {\tt ESMF\_Clock}
215!     
216!     The arguments are:
217!     \begin{description}
218!     \item[clock]
219!          The object instance to initialize
220!     \item[{[TimeStep]}]
221!          The {\tt ESMF\_Clock}'s time step interval
222!     \item[StartTime]
223!          The {\tt ESMF\_Clock}'s starting time
224!     \item[StopTime]
225!          The {\tt ESMF\_Clock}'s stopping time
226!     \item[{[RefTime]}]
227!          The {\tt ESMF\_Clock}'s reference time
228!     \item[{[rc]}]
229!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
230!     \end{description}
231!     
232! !REQUIREMENTS:
233!     TMG3.1, TMG3.4.4
234!EOP
235      ierr = ESMF_SUCCESS
236      IF ( PRESENT(TimeStep) ) THEN
237        CALL ESMF_ClockSetTimeStep ( clock, TimeStep, rc=ierr )
238      ENDIF
239      IF ( PRESENT(RefTime) ) clock%clockint%RefTime = RefTime
240      IF ( PRESENT(StartTime) ) clock%clockint%StartTime = StartTime
241      IF ( PRESENT(StopTime) ) clock%clockint%StopTime = StopTime
242      IF ( PRESENT(CurrTime) ) THEN
243        CALL ESMF_ClockSetCurrTime(clock, CurrTime, rc=ierr)
244      ENDIF
245      IF ( PRESENT(rc) ) rc = ierr
246
247      end subroutine ESMF_ClockSet
248
249
250! Create ESMF_Clock using ESMF 2.1.0+ semantics
251      FUNCTION ESMF_ClockCreate( name, TimeStep, StartTime, StopTime, &
252                                 RefTime, rc )
253        ! return value
254        type(ESMF_Clock) :: ESMF_ClockCreate
255        ! !ARGUMENTS:
256        character (len=*),       intent(in),  optional :: name
257        type(ESMF_TimeInterval), intent(in), optional :: TimeStep
258        type(ESMF_Time), intent(in) :: StartTime
259        type(ESMF_Time), intent(in) :: StopTime
260        type(ESMF_Time), intent(in), optional :: RefTime
261        integer, intent(out), optional :: rc
262        ! locals
263        type(ESMF_Clock) :: clocktmp
264         ! TBH:  ignore allocate errors, for now
265        ALLOCATE( clocktmp%clockint )
266        CALL ESMF_ClockSetOLD( clocktmp%clockint,   &
267                               TimeStep= TimeStep,  &
268                               StartTime=StartTime, &
269                               StopTime= StopTime,  &
270                               RefTime=RefTime, rc=rc )
271        ESMF_ClockCreate = clocktmp
272      END FUNCTION ESMF_ClockCreate
273
274
275! Deallocate memory for ESMF_Clock
276      SUBROUTINE ESMF_ClockDestroy( clock, rc )
277         TYPE(ESMF_Clock), INTENT(INOUT) :: clock
278         INTEGER,          INTENT(  OUT), OPTIONAL :: rc
279         ! TBH:  ignore deallocate errors, for now
280         DEALLOCATE( clock%clockint%AlarmList )
281         DEALLOCATE( clock%clockint )
282         IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
283      END SUBROUTINE ESMF_ClockDestroy
284
285
286!------------------------------------------------------------------------------
287!BOP
288! !IROUTINE: ESMF_ClockGet - Get clock properties -- for compatibility with ESMF 2.0.1
289
290! !INTERFACE:
291      subroutine ESMF_ClockGet(clock, StartTime, CurrTime,       &
292                               AdvanceCount, StopTime, TimeStep, &
293                               PrevTime, RefTime, &
294                               rc)
295
296! !ARGUMENTS:
297      type(ESMF_Clock), intent(in) :: clock
298      type(ESMF_Time), intent(out), optional :: StartTime
299      type(ESMF_Time), intent(out), optional :: CurrTime
300      type(ESMF_Time), intent(out), optional :: StopTime
301      type(ESMF_Time), intent(out), optional :: PrevTime
302      type(ESMF_Time), intent(out), optional :: RefTime
303      integer(ESMF_KIND_I8), intent(out), optional :: AdvanceCount
304      type(ESMF_TimeInterval), intent(out), optional :: TimeStep
305      integer, intent(out), optional :: rc
306      integer :: ierr
307
308! !DESCRIPTION:
309!     Returns the number of times the {\tt ESMF\_Clock} has been advanced
310!     (time stepped)
311!
312!     The arguments are:
313!     \begin{description}
314!     \item[clock]
315!          The object instance to get the advance count from
316!     \item[StartTime]
317!          The start time
318!     \item[CurrTime]
319!          The current time
320!     \item[AdvanceCount]
321!          The number of times the {\tt ESMF\_Clock} has been advanced
322!     \item[StopTime]
323!          The {\tt ESMF\_Clock}'s stopping time
324!     \item[{[TimeStep]}]
325!          The {\tt ESMF\_Clock}'s time step interval
326!     \item[{[PrevTime]}]
327!          The {\tt ESMF\_Clock}'s previous current time
328!     \item[{[PrevTime]}]
329!          The {\tt ESMF\_Clock}'s reference time
330!     \item[{[rc]}]
331!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
332!     \end{description}
333
334! !REQUIREMENTS:
335!     TMG3.5.1
336!EOP
337      ierr = ESMF_SUCCESS
338
339      IF ( PRESENT (StartTime) ) THEN
340        CALL ESMF_ClockGetStartTime( clock, StartTime=StartTime, rc=ierr )
341      ENDIF
342      IF ( PRESENT (CurrTime) ) THEN
343        CALL ESMF_ClockGetCurrTime( clock , CurrTime, ierr )
344      ENDIF
345      IF ( PRESENT (StopTime) ) THEN
346        CALL ESMF_ClockGetStopTime( clock , StopTime, ierr )
347      ENDIF
348      IF ( PRESENT (AdvanceCount) ) THEN
349        CALL ESMF_ClockGetAdvanceCount(clock, AdvanceCount, ierr)
350      ENDIF
351      IF ( PRESENT (TimeStep) ) THEN
352        CALL ESMF_ClockGetTimeStep(clock, TimeStep, ierr)
353      ENDIF
354      IF ( PRESENT (PrevTime) ) THEN
355        CALL ESMF_ClockGetPrevTime(clock, PrevTime, ierr)
356      ENDIF
357      IF ( PRESENT (RefTime) ) THEN
358        CALL ESMF_ClockGetRefTime(clock, RefTime, ierr)
359      ENDIF
360
361      IF ( PRESENT (rc) ) THEN
362        rc = ierr
363      ENDIF
364   
365      end subroutine ESMF_ClockGet
366
367
368! !IROUTINE: ESMF_ClockGetAdvanceCount - Get the clock's advance count
369
370! !INTERFACE:
371      subroutine ESMF_ClockGetAdvanceCount(clock, AdvanceCount, rc)
372
373! !ARGUMENTS:
374      type(ESMF_Clock), intent(in) :: clock
375      integer(ESMF_KIND_I8), intent(out) :: AdvanceCount
376      integer, intent(out), optional :: rc
377
378! !DESCRIPTION:
379!     Returns the number of times the {\tt ESMF\_Clock} has been advanced
380!     (time stepped)
381!
382!     The arguments are:
383!     \begin{description}
384!     \item[clock]
385!          The object instance to get the advance count from
386!     \item[AdvanceCount]
387!          The number of times the {\tt ESMF\_Clock} has been advanced
388!     \item[{[rc]}]
389!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
390!     \end{description}
391
392! !REQUIREMENTS:
393!     TMG3.5.1
394!EOP
395
396      AdvanceCount = clock%clockint%AdvanceCount
397
398      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
399   
400      end subroutine ESMF_ClockGetAdvanceCount
401
402!------------------------------------------------------------------------------
403!BOP
404! !IROUTINE: ESMF_ClockGetTimeStep - Get a clock's timestep interval
405
406! !INTERFACE:
407      subroutine ESMF_ClockGetTimeStep(clock, TimeStep, rc)
408
409! !ARGUMENTS:
410      type(ESMF_Clock), intent(in) :: clock
411      type(ESMF_TimeInterval), intent(out) :: TimeStep
412      integer, intent(out), optional :: rc
413
414! !DESCRIPTION:
415!     Get an {\tt ESMF\_Clock}'s timestep interval
416!
417!     The arguments are:
418!     \begin{description}
419!     \item[clock]
420!          The object instance to get the time step from
421!     \item[TimeStep]
422!          The time step
423!     \item[{[rc]}]
424!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
425!     \end{description}
426!
427! !REQUIREMENTS:
428!     TMG3.5.2
429!EOP
430
431      TimeStep = clock%clockint%TimeStep
432      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
433   
434      end subroutine ESMF_ClockGetTimeStep
435
436!------------------------------------------------------------------------------
437!BOP
438! !IROUTINE: ESMF_ClockSetTimeStep - Set a clock's timestep interval
439
440! !INTERFACE:
441      subroutine ESMF_ClockSetTimeStep(clock, TimeStep, rc)
442
443! !ARGUMENTS:
444      type(ESMF_Clock), intent(inout) :: clock  ! really INTENT(OUT)
445      type(ESMF_TimeInterval), intent(in) :: TimeStep
446      integer, intent(out), optional      :: rc
447
448! !DESCRIPTION:
449!     Set an {\tt ESMF\_Clock}'s timestep interval
450!
451!     The arguments are:
452!     \begin{description}
453!     \item[clock]
454!          The object instance to set the time step
455!     \item[TimeStep]
456!          The time step
457!     \item[{[rc]}]
458!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
459!     \end{description}
460!
461! !REQUIREMENTS:
462!     TMG3.4.2
463!EOP
464
465      clock%clockint%TimeStep = TimeStep
466      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
467
468      end subroutine ESMF_ClockSetTimeStep
469
470!------------------------------------------------------------------------------
471!BOP
472! !IROUTINE: ESMF_ClockGetCurrTime - Get a clock's current time
473
474! !INTERFACE:
475      subroutine ESMF_ClockGetCurrTime(clock, CurrTime, rc)
476
477! !ARGUMENTS:
478      type(ESMF_Clock), intent(in) :: clock
479      type(ESMF_Time), intent(out) :: CurrTime
480      integer, intent(out), optional :: rc
481
482! !DESCRIPTION:
483!     Get an {\tt ESMF\_Clock}'s current time     
484!
485!     The arguments are:
486!     \begin{description}
487!     \item[clock]
488!          The object instance to get the current time from
489!     \item[CurrTime]
490!          The current time
491!     \item[{[rc]}]
492!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
493!     \end{description}
494!
495! !REQUIREMENTS:
496!     TMG3.5.4
497!EOP
498
499      CurrTime = clock%clockint%CurrTime
500      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
501      end subroutine ESMF_ClockGetCurrTime
502
503!------------------------------------------------------------------------------
504!BOP
505! !IROUTINE: ESMF_ClockSetCurrTime - Set a clock's current time
506
507! !INTERFACE:
508      subroutine ESMF_ClockSetCurrTime(clock, CurrTime, rc)
509
510! !ARGUMENTS:
511      type(ESMF_Clock), intent(inout) :: clock  ! really INTENT(OUT)
512      type(ESMF_Time), intent(in) :: CurrTime
513      integer, intent(out), optional :: rc
514
515! !DESCRIPTION:
516!     Set an {\tt ESMF\_Clock}'s current time
517!
518!     The arguments are:
519!     \begin{description}
520!     \item[clock]
521!          The object instance to set the current time from
522!     \item[CurrTime]
523!          The current time
524!     \item[{[rc]}]
525!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
526!     \end{description}
527!
528! !REQUIREMENTS:
529!     TMG3.4.3
530!EOP
531
532      clock%clockint%CurrTime = CurrTime
533      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
534   
535      end subroutine ESMF_ClockSetCurrTime
536
537!------------------------------------------------------------------------------
538!BOP
539! !IROUTINE: ESMF_ClockGetStartTime - Get a clock's start time
540
541! !INTERFACE:
542      subroutine ESMF_ClockGetStartTime(clock, StartTime, rc)
543
544! !ARGUMENTS:
545      type(ESMF_Clock), intent(in) :: clock
546      type(ESMF_Time), intent(out) :: StartTime
547      integer, intent(out), optional :: rc
548
549! !DESCRIPTION:
550!     Get an {\tt ESMF\_Clock}'s start time
551!
552!     The arguments are:
553!     \begin{description}
554!     \item[clock]
555!          The object instance to get the start time from
556!     \item[StartTime]
557!          The start time
558!     \item[{[rc]}]
559!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
560!     \end{description}
561!
562! !REQUIREMENTS:
563!     TMG3.5.3
564!EOP
565
566      StartTime = clock%clockint%StartTime
567      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
568   
569      end subroutine ESMF_ClockGetStartTime
570
571!------------------------------------------------------------------------------
572!BOP
573! !IROUTINE: ESMF_ClockGetStopTime - Get a clock's stop time
574
575! !INTERFACE:
576      subroutine ESMF_ClockGetStopTime(clock, StopTime, rc)
577
578! !ARGUMENTS:
579      type(ESMF_Clock), intent(in) :: clock
580      type(ESMF_Time), intent(out) :: StopTime
581      integer, intent(out), optional :: rc
582
583! !DESCRIPTION:
584!     Get an {\tt ESMF\_Clock}'s stop time
585!
586!     The arguments are:
587!     \begin{description}
588!     \item[clock]
589!          The object instance to get the stop time from
590!     \item[StopTime]
591!          The stop time
592!     \item[{[rc]}]
593!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
594!     \end{description}
595!
596! !REQUIREMENTS:
597!     TMG3.5.3
598!EOP
599
600      StopTime = clock%clockint%StopTime
601      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
602   
603      end subroutine ESMF_ClockGetStopTime
604
605!------------------------------------------------------------------------------
606!BOP
607! !IROUTINE: ESMF_ClockGetRefTime - Get a clock's reference time
608
609! !INTERFACE:
610      subroutine ESMF_ClockGetRefTime(clock, RefTime, rc)
611
612! !ARGUMENTS:
613      type(ESMF_Clock), intent(in) :: clock
614      type(ESMF_Time), intent(out) :: RefTime
615      integer, intent(out), optional :: rc
616
617! !DESCRIPTION:
618!     Get an {\tt ESMF\_Clock}'s reference time
619!
620!     The arguments are:
621!     \begin{description}
622!     \item[clock]
623!          The object instance to get the reference time from
624!     \item[RefTime]
625!          The reference time
626!     \item[{[rc]}]
627!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
628!     \end{description}
629!
630! !REQUIREMENTS:
631!     TMG3.5.3
632!EOP
633      refTime = clock%clockint%RefTime
634      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
635      end subroutine ESMF_ClockGetRefTime
636
637!------------------------------------------------------------------------------
638!BOP
639! !IROUTINE: ESMF_ClockGetPrevTime - Get a clock's previous current time
640
641! !INTERFACE:
642      subroutine ESMF_ClockGetPrevTime(clock, PrevTime, rc)
643
644! !ARGUMENTS:
645      type(ESMF_Clock), intent(in) :: clock
646      type(ESMF_Time), intent(out) :: PrevTime
647      integer, intent(out), optional :: rc
648
649! !DESCRIPTION:
650!     Get an {\tt ESMF\_Clock}'s previous current time
651!
652!     The arguments are:
653!     \begin{description}
654!     \item[clock]
655!          The object instance to get the previous current time from
656!     \item[PrevTime]
657!          The previous current time
658!     \item[{[rc]}]
659!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
660!     \end{description}
661!
662! !REQUIREMENTS:
663!     TMG3.5.4
664!EOP
665
666! hack for bug in PGI 5.1-x
667!      prevTime = Clock%clockint%CurrTime - Clock%clockint%TimeStep
668      prevTime = ESMF_TimeDec( Clock%clockint%CurrTime, &
669                               Clock%clockint%TimeStep )
670
671      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
672      end subroutine ESMF_ClockGetPrevTime
673
674!------------------------------------------------------------------------------
675!BOP
676! !IROUTINE: ESMF_ClockGetCurrSimTime - Get a clock's current simulation time
677
678! !INTERFACE:
679      subroutine ESMF_ClockGetCurrSimTime(clock, CurrSimTime, rc)
680
681! !ARGUMENTS:
682      type(ESMF_Clock), intent(in) :: clock
683      type(ESMF_TimeInterval), intent(out) :: CurrSimTime
684      integer, intent(out), optional :: rc
685
686! !DESCRIPTION:
687!     Get an {\tt ESMF\_Clock}'s current simulation time
688!
689!     The arguments are:
690!     \begin{description}
691!     \item[clock]
692!          The object instance to get the current simulation time from
693!     \item[CurrSimTime]
694!          The current simulation time
695!     \item[{[rc]}]
696!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
697!     \end{description}
698!
699! !REQUIREMENTS:
700!     TMG3.5.5
701!EOP
702      CALL wrf_error_fatal( 'ESMF_ClockGetCurrSimTime not supported' )
703      end subroutine ESMF_ClockGetCurrSimTime
704
705!------------------------------------------------------------------------------
706!BOP
707! !IROUTINE: ESMF_ClockGetPrevSimTime - Get a clock's previous simulation time
708
709! !INTERFACE:
710      subroutine ESMF_ClockGetPrevSimTime(clock, PrevSimTime, rc)
711
712! !ARGUMENTS:
713      type(ESMF_Clock), intent(in) :: clock
714      type(ESMF_TimeInterval), intent(out) :: PrevSimTime
715      integer, intent(out), optional :: rc
716
717! !DESCRIPTION:
718!     Get an {\tt ESMF\_Clock}'s previous simulation time
719!
720!     The arguments are:
721!     \begin{description}
722!     \item[clock]
723!          The object instance to get the previous simulation time from
724!     \item[PrevSimTime]
725!          The previous simulation time
726!     \item[{[rc]}]
727!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
728!     \end{description}
729!
730! !REQUIREMENTS:
731!     TMG3.5.5
732!EOP
733      CALL wrf_error_fatal( 'ESMF_ClockGetPrevSimTime not supported' )
734      end subroutine ESMF_ClockGetPrevSimTime
735
736!------------------------------------------------------------------------------
737!BOP
738! !IROUTINE: ESMF_ClockAddAlarm - Add an alarm to a clock's alarm list
739
740! !INTERFACE:
741      subroutine ESMF_ClockAddAlarm(clock, Alarm, rc)
742
743! !ARGUMENTS:
744      type(ESMF_Clock), intent(inout) :: clock
745      type(ESMF_Alarm), intent(inout) :: Alarm
746      integer, intent(out), optional :: rc
747
748! !DESCRIPTION:
749!     Add an {\tt ESMF\_Alarm} to an {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list
750!
751!     The arguments are:
752!     \begin{description}
753!     \item[clock]
754!          The object instance to add an {\tt ESMF\_Alarm} to
755!     \item[Alarm]
756!          The {\tt ESMF\_Alarm} to add to the {\tt ESMF\_Clock}'s
757!          {\tt ESMF\_Alarm} list
758!     \item[{[rc]}]
759!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
760!     \end{description}
761!   
762! !REQUIREMENTS:
763!     TMG4.1, TMG4.2
764!EOP
765   
766      IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
767      clock%clockint%NumAlarms = clock%clockint%NumAlarms + 1
768      IF ( clock%clockint%NumAlarms > SIZE (clock%clockint%AlarmList) ) THEN
769        CALL wrf_error_fatal ( 'ESMF_ClockAddAlarm:  too many alarms' )
770      ELSE IF ( .NOT. ASSOCIATED( Alarm%alarmint ) ) THEN
771        CALL wrf_error_fatal ( &
772               'ESMF_ClockAddAlarm:  alarm not created' )
773      ELSE
774        IF ( Alarm%alarmint%RingTimeSet ) THEN
775           Alarm%alarmint%PrevRingTime = Alarm%alarmint%RingTime
776        ELSE
777!TBH:  This has the nasty side-effect of forcing us to explicitly turn on
778!TBH:  alarms that are created with RingInterval only, if we want them to start
779!TBH:  ringing right away.  And this is done (see
780!TBH:  COMPUTE_VORTEX_CENTER_ALARM).  Straighten this out... 
781           Alarm%alarmint%PrevRingTime = clock%clockint%CurrTime
782        ENDIF
783        Alarm%alarmint%Ringing = .FALSE.
784
785        ! finally, load the alarm into the list
786        clock%clockint%AlarmList(clock%clockint%NumAlarms) = Alarm
787      ENDIF
788   
789      end subroutine ESMF_ClockAddAlarm
790
791!------------------------------------------------------------------------------
792!BOP
793! !IROUTINE: ESMF_ClockGetAlarmList - Get a clock's alarm list
794
795! !INTERFACE:
796      subroutine ESMF_ClockGetAlarmList(clock, AlarmList, rc)
797
798! !ARGUMENTS:
799      type(ESMF_Clock), intent(in) :: clock
800      type(ESMF_Alarm), pointer :: AlarmList(:)
801      integer, intent(out), optional :: rc
802
803! !DESCRIPTION:
804!     Get an {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list     
805!   
806!     The arguments are:
807!     \begin{description}
808!     \item[clock]
809!          The object instance to get the {\tt ESMF\_Alarm} list from
810!     \item[AlarmList]
811!          The {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list
812!     \item[{[rc]}]
813!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
814!     \end{description}
815!   
816! !REQUIREMENTS:
817!     TMG4.3
818!EOP
819
820      AlarmList => clock%clockint%AlarmList
821      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
822
823      end subroutine ESMF_ClockGetAlarmList
824
825!------------------------------------------------------------------------------
826!BOP
827! !IROUTINE: ESMF_ClockGetNumAlarms - Get the number of alarms in a clock's alarm list
828
829! !INTERFACE:
830      subroutine ESMF_ClockGetNumAlarms(clock, NumAlarms, rc)
831
832! !ARGUMENTS:
833      type(ESMF_Clock), intent(in) :: clock
834      integer, intent(out) :: NumAlarms
835      integer, intent(out), optional :: rc
836
837! !DESCRIPTION:
838!     Get the number of {\tt ESMF\_Alarm}s in an {\tt ESMF\_Clock}'s
839!       {\tt ESMF\_Alarm} list     
840!   
841!     The arguments are:
842!     \begin{description}
843!     \item[clock]
844!          The object instance to get the number of {\tt ESMF\_Alarm}s from
845!     \item[NumAlarms]
846!          The number of {\tt ESMF\_Alarm}s in the {\tt ESMF\_Clock}'s
847!            {\tt ESMF\_Alarm} list
848!     \item[{[rc]}]
849!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
850!     \end{description}
851!   
852! !REQUIREMENTS:
853!     TMG4.3
854!EOP
855
856      NumAlarms = clock%clockint%NumAlarms
857      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
858   
859      end subroutine ESMF_ClockGetNumAlarms
860
861!------------------------------------------------------------------------------
862!BOP
863! !IROUTINE: ESMF_ClockSyncToWallClock - Set clock's current time to wall clock time
864
865! !INTERFACE:
866      subroutine ESMF_ClockSyncToWallClock(clock, rc)
867
868! !ARGUMENTS:
869      type(ESMF_Clock), intent(inout) :: clock
870      integer, intent(out), optional :: rc
871   
872! !DESCRIPTION:
873!     Set an {\tt ESMF\_Clock}'s current time to wall clock time     
874!   
875!     The arguments are:
876!     \begin{description}
877!     \item[clock]
878!          The object instance to synchronize to wall clock time
879!     \item[{[rc]}]
880!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
881!     \end{description}
882!   
883! !REQUIREMENTS:
884!     TMG3.4.5
885!EOP
886      CALL wrf_error_fatal( 'ESMF_ClockSyncToWallClock not supported' )
887      end subroutine ESMF_ClockSyncToWallClock
888
889!------------------------------------------------------------------------------
890!BOP
891! !IROUTINE: ESMF_ClockAdvance - Advance a clock's current time by one time step
892
893! !INTERFACE:
894      subroutine ESMF_ClockAdvance(clock, RingingAlarmList, &
895                                   NumRingingAlarms, rc)
896
897use esmf_timemod
898
899! !ARGUMENTS:
900      type(ESMF_Clock), intent(inout) :: clock
901      type(ESMF_Alarm), dimension(MAX_ALARMS), intent(out), optional :: &
902                                        RingingAlarmList
903      integer, intent(out), optional :: NumRingingAlarms
904      integer, intent(out), optional :: rc
905! Local
906      logical pred1, pred2, pred3
907      integer i, n
908      type(ESMF_Alarm) :: alarm
909      logical :: positive_timestep
910!   
911! !DESCRIPTION:
912!     Advance an {\tt ESMF\_Clock}'s current time by one time step
913
914!     The arguments are:
915!     \begin{description}
916!     \item[clock]
917!          The object instance to advance
918!     \item[{[RingingAlarmList]}]
919!          Return a list of any ringing alarms after the time step
920!     \item[{[NumRingingAlarms]}]
921!          The number of ringing alarms returned
922!     \item[{[rc]}]
923!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
924!     \end{description}
925
926! !REQUIREMENTS:
927!     TMG3.4.1
928!EOP
929! hack for bug in PGI 5.1-x
930!      clock%clockint%CurrTime = clock%clockint%CurrTime + &
931!                                clock%clockint%TimeStep
932      clock%clockint%CurrTime = ESMF_TimeInc( clock%clockint%CurrTime, &
933                                              clock%clockint%TimeStep )
934      positive_timestep = ESMF_TimeIntervalIsPositive( clock%clockint%TimeStep )
935
936      IF ( Present(NumRingingAlarms) ) NumRingingAlarms = 0
937      clock%clockint%AdvanceCount = clock%clockint%AdvanceCount + 1
938      DO i = 1, MAX_ALARMS
939        alarm = clock%clockint%AlarmList(i)
940        ! TBH:  This is really dangerous.  We need to be able to NULLIFY
941        ! TBH:  alarmint at compile-time (F95 synax) to make this safe. 
942!$$$TBH:  see if F95 compile-time pointer-nullification is supported by all
943!$$$TBH:  compilers we support
944        IF ( ASSOCIATED( alarm%alarmint ) ) THEN
945          IF ( alarm%alarmint%Enabled ) THEN
946            IF ( alarm%alarmint%RingIntervalSet ) THEN
947              pred1 = .FALSE. ; pred2 = .FALSE. ; pred3 = .FALSE.
948              ! alarm cannot ring if clock has passed the alarms stop time
949              IF ( alarm%alarmint%StopTimeSet ) THEN
950                IF ( positive_timestep ) THEN
951! hack for bug in PGI 5.1-x
952!                  PRED1 = clock%clockint%CurrTime > alarm%alarmint%StopTime
953                  PRED1 = ESMF_TimeGT( clock%clockint%CurrTime, &
954                                       alarm%alarmint%StopTime )
955                ELSE
956                  ! in this case time step is negative and stop time is
957                  ! less than start time
958!                  PRED1 = clock%clockint%CurrTime < alarm%alarmint%StopTime
959                  PRED1 = ESMF_TimeLT( clock%clockint%CurrTime, &
960                                       alarm%alarmint%StopTime )
961                ENDIF
962              ENDIF
963              ! one-shot alarm:  check for ring time
964! TBH:  Need to remove duplicated code.  Need to enforce only one of
965! TBH:  alarm%alarmint%RingTimeSet or alarm%alarmint%RingIntervalSet ever
966! TBH:  being .TRUE. and simplify the logic.  Also, the simpler
967! TBH:  implementation in the duplicated code below should be sufficient. 
968              IF ( alarm%alarmint%RingTimeSet ) THEN
969                IF ( positive_timestep ) THEN
970! hack for bug in PGI 5.1-x
971!                   PRED2 = ( alarm%alarmint%RingTime <= clock%clockint%CurrTime     &
972!                          .AND. clock%clockint%CurrTime < alarm%alarmint%RingTime + &
973!                                clock%clockint%TimeStep )
974                   PRED2 = ( ESMF_TimeLE( alarm%alarmint%RingTime,       &
975                                          clock%clockint%CurrTime )      &
976                             .AND. ESMF_TimeLT( clock%clockint%CurrTime, &
977                               ESMF_TimeInc( alarm%alarmint%RingTime,    &
978                                             clock%clockint%TimeStep ) ) )
979                ELSE
980                  ! in this case time step is negative and stop time is
981                  ! less than start time
982! hack for bug in PGI 5.1-x
983!                   PRED2 = ( alarm%alarmint%RingTime >= clock%clockint%CurrTime     &
984!                          .AND. clock%clockint%CurrTime > alarm%alarmint%RingTime + &
985!                                clock%clockint%TimeStep )
986                   PRED2 = ( ESMF_TimeGE( alarm%alarmint%RingTime,       &
987                                          clock%clockint%CurrTime )      &
988                             .AND. ESMF_TimeGT( clock%clockint%CurrTime, &
989                               ESMF_TimeInc( alarm%alarmint%RingTime,    &
990                                             clock%clockint%TimeStep ) ) )
991                ENDIF
992              ENDIF
993              ! repeating alarm:  check for ring interval
994              IF ( alarm%alarmint%RingIntervalSet ) THEN
995                IF ( positive_timestep ) THEN
996! hack for bug in PGI 5.1-x
997!                   PRED3 = ( alarm%alarmint%PrevRingTime + alarm%alarmint%RingInterval <= &
998!                             clock%clockint%CurrTime )
999
1000                   PRED3 = ( ESMF_TimeLE( ESMF_TimeInc(                  &
1001                                          alarm%alarmint%PrevRingTime,   &
1002                                          alarm%alarmint%RingInterval ), &
1003                             clock%clockint%CurrTime ) )
1004                ELSE
1005                  ! in this case time step is negative and stop time is
1006                  ! less than start time
1007                  ! ring interval must always be positive
1008! hack for bug in PGI 5.1-x
1009!                   PRED3 = ( alarm%alarmint%PrevRingTime - alarm%alarmint%RingInterval >= &
1010!                             clock%clockint%CurrTime )
1011
1012                   PRED3 = ( ESMF_TimeGE( ESMF_TimeDec(                  &
1013                                          alarm%alarmint%PrevRingTime,   &
1014                                          alarm%alarmint%RingInterval ), &
1015                             clock%clockint%CurrTime ) )
1016                ENDIF
1017              ENDIF
1018              IF ( ( .NOT. ( pred1 ) ) .AND. &
1019                   ( ( pred2 ) .OR. ( pred3 ) ) ) THEN
1020                 alarm%alarmint%Ringing = .TRUE.
1021                 IF ( positive_timestep ) THEN
1022! hack for bug in PGI 5.1-x
1023!                   IF ( PRED3) alarm%alarmint%PrevRingTime = alarm%alarmint%PrevRingTime + &
1024!                                                    alarm%alarmint%RingInterval
1025                   IF ( PRED3 )                                   &
1026                     alarm%alarmint%PrevRingTime =                &
1027                       ESMF_TimeInc( alarm%alarmint%PrevRingTime, &
1028                                     alarm%alarmint%RingInterval )
1029                 ELSE
1030                   ! in this case time step is negative and stop time is
1031                   ! less than start time
1032                   ! ring interval must always be positive
1033! hack for bug in PGI 5.1-x
1034!                   IF ( PRED3) alarm%alarmint%PrevRingTime = alarm%alarmint%PrevRingTime - &
1035!                                                    alarm%alarmint%RingInterval
1036                   IF ( PRED3 )                                   &
1037                     alarm%alarmint%PrevRingTime =                &
1038                       ESMF_TimeDec( alarm%alarmint%PrevRingTime, &
1039                                     alarm%alarmint%RingInterval )
1040                 ENDIF
1041                 IF ( PRESENT( RingingAlarmList ) .AND. &
1042                      PRESENT ( NumRingingAlarms ) ) THEN
1043                   NumRingingAlarms = NumRingingAlarms + 1
1044                   RingingAlarmList( NumRingingAlarms ) = alarm
1045                 ENDIF
1046              ENDIF
1047            ELSE IF ( alarm%alarmint%RingTimeSet ) THEN
1048! TBH:  Need to remove duplicated code.  Need to enforce only one of
1049! TBH:  alarm%alarmint%RingTimeSet or alarm%alarmint%RingIntervalSet ever
1050! TBH:  being .TRUE. and simplify the logic.  Also, the simpler
1051! TBH:  implementation in here should be sufficient. 
1052              IF ( positive_timestep ) THEN
1053! hack for bug in PGI 5.1-x
1054!                IF ( alarm%alarmint%RingTime <= clock%clockint%CurrTime ) THEN
1055                IF ( ESMF_TimeLE( alarm%alarmint%RingTime, &
1056                                  clock%clockint%CurrTime ) ) THEN
1057                   alarm%alarmint%Ringing = .TRUE.
1058                   IF ( PRESENT( RingingAlarmList ) .AND. &
1059                        PRESENT ( NumRingingAlarms ) ) THEN
1060                     NumRingingAlarms = NumRingingAlarms + 1
1061                     RingingAlarmList( NumRingingAlarms ) = alarm
1062                   ENDIF
1063                ENDIF
1064              ELSE
1065                ! in this case time step is negative and stop time is
1066                ! less than start time
1067! hack for bug in PGI 5.1-x
1068!                IF ( alarm%alarmint%RingTime >= clock%clockint%CurrTime ) THEN
1069                IF ( ESMF_TimeGE( alarm%alarmint%RingTime, &
1070                                  clock%clockint%CurrTime ) ) THEN
1071                   alarm%alarmint%Ringing = .TRUE.
1072                   IF ( PRESENT( RingingAlarmList ) .AND. &
1073                        PRESENT ( NumRingingAlarms ) ) THEN
1074                     NumRingingAlarms = NumRingingAlarms + 1
1075                     RingingAlarmList( NumRingingAlarms ) = alarm
1076                   ENDIF
1077                ENDIF
1078              ENDIF
1079            ENDIF
1080            IF ( alarm%alarmint%StopTimeSet ) THEN
1081! TBH:  what is this for??? 
1082            ENDIF
1083          ENDIF
1084        ENDIF
1085        clock%clockint%AlarmList(i) = alarm
1086      ENDDO
1087      IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
1088   
1089      end subroutine ESMF_ClockAdvance
1090
1091!------------------------------------------------------------------------------
1092!BOP
1093! !IROUTINE: ESMF_ClockStopTimeDisable - NOOP for compatibility with ESMF 2.1.0+
1094
1095! !INTERFACE:
1096      subroutine ESMF_ClockStopTimeDisable(clock, rc)
1097!
1098! !ARGUMENTS:
1099      type(ESMF_Clock), intent(in) :: clock
1100      integer, intent(out), optional :: rc
1101
1102      rc = ESMF_SUCCESS
1103
1104      end subroutine ESMF_ClockStopTimeDisable
1105
1106!------------------------------------------------------------------------------
1107!BOP
1108! !IROUTINE: ESMF_ClockIsStopTime - Has the clock reached its stop time ?
1109
1110! !INTERFACE:
1111      function ESMF_ClockIsStopTime(clock, rc)
1112!
1113! !RETURN VALUE:
1114      logical :: ESMF_ClockIsStopTime
1115
1116! !ARGUMENTS:
1117      type(ESMF_Clock), intent(in) :: clock
1118      integer, intent(out), optional :: rc
1119      logical :: positive_timestep
1120
1121! !DESCRIPTION:
1122!     Return true if {\tt ESMF\_Clock} has reached its stop time, false
1123!     otherwise     
1124!
1125!     The arguments are:
1126!     \begin{description}
1127!     \item[clock]
1128!          The object instance to check
1129!     \item[{[rc]}]
1130!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1131!     \end{description}
1132
1133! !REQUIREMENTS:
1134!     TMG3.5.6
1135!EOP
1136
1137      positive_timestep = ESMF_TimeIntervalIsPositive( clock%clockint%TimeStep )
1138      IF ( positive_timestep ) THEN
1139! hack for bug in PGI 5.1-x
1140!        if ( clock%clockint%CurrTime .GE. clock%clockint%StopTime ) THEN
1141        if ( ESMF_TimeGE( clock%clockint%CurrTime, &
1142                          clock%clockint%StopTime ) ) THEN
1143          ESMF_ClockIsStopTime = .TRUE.
1144        else
1145          ESMF_ClockIsStopTime = .FALSE.
1146        endif
1147      ELSE
1148! hack for bug in PGI 5.1-x
1149!        if ( clock%clockint%CurrTime .LE. clock%clockint%StopTime ) THEN
1150        if ( ESMF_TimeLE( clock%clockint%CurrTime, &
1151                          clock%clockint%StopTime ) ) THEN
1152          ESMF_ClockIsStopTime = .TRUE.
1153        else
1154          ESMF_ClockIsStopTime = .FALSE.
1155        endif
1156      ENDIF
1157      IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
1158   
1159      end function ESMF_ClockIsStopTime
1160
1161!------------------------------------------------------------------------------
1162!
1163! This section defines the overridden Read, Write, Validate and Print methods
1164! from the ESMF_Base class
1165!
1166!------------------------------------------------------------------------------
1167!BOP
1168! !IROUTINE: ESMF_ClockRead - Restores a clock
1169
1170! !INTERFACE:
1171      subroutine ESMF_ClockRead(clock, TimeStep, StartTime, StopTime, &
1172                                RefTime, CurrTime, PrevTime, AdvanceCount, &
1173                                AlarmList, rc)
1174
1175! !ARGUMENTS:
1176      type(ESMF_Clock), intent(out) :: clock
1177      type(ESMF_TimeInterval), intent(in) :: TimeStep
1178      type(ESMF_Time), intent(in) :: StartTime
1179      type(ESMF_Time), intent(in) :: StopTime
1180      type(ESMF_Time), intent(in) :: RefTime
1181      type(ESMF_Time), intent(in) :: CurrTime
1182      type(ESMF_Time), intent(in) :: PrevTime
1183      integer(ESMF_KIND_I8), intent(in) :: AdvanceCount
1184      type(ESMF_Alarm), dimension(MAX_ALARMS), intent(in) :: AlarmList
1185      integer, intent(out), optional :: rc
1186   
1187! !DESCRIPTION:
1188!     Restore an {\tt ESMF\_Clock}
1189!     
1190!     The arguments are:
1191!     \begin{description}
1192!     \item[clock]
1193!          The object instance to restore
1194!     \item[TimeStep]
1195!          The {\tt ESMF\_Clock}'s time step interval
1196!     \item[StartTime]
1197!          The {\tt ESMF\_Clock}'s starting time
1198!     \item[StopTime]
1199!          The {\tt ESMF\_Clock}'s stopping time
1200!     \item[RefTime]
1201!          The {\tt ESMF\_Clock}'s reference time
1202!     \item[CurrTime]
1203!          The {\tt ESMF\_Clock}'s current time
1204!     \item[PrevTime]
1205!          The {\tt ESMF\_Clock}'s previous time
1206!     \item[AdvanceCount]
1207!          The number of times the {\tt ESMF\_Clock} has been advanced
1208!     \item[AlarmList]
1209!          The {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list
1210!     \item[{[rc]}]
1211!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1212!     \end{description}
1213!     
1214! !REQUIREMENTS:
1215!EOP
1216      CALL wrf_error_fatal( 'ESMF_ClockRead not supported' )
1217      end subroutine ESMF_ClockRead
1218
1219!------------------------------------------------------------------------------
1220!BOP
1221! !IROUTINE: ESMF_ClockWrite - Saves a clock
1222
1223! !INTERFACE:
1224      subroutine ESMF_ClockWrite(clock, TimeStep, StartTime, StopTime, &
1225                            RefTime, CurrTime, PrevTime, AdvanceCount, &
1226                            AlarmList, rc)
1227
1228! !ARGUMENTS:
1229      type(ESMF_Clock), intent(in) :: clock
1230      type(ESMF_TimeInterval), intent(out) :: TimeStep
1231      type(ESMF_Time), intent(out) :: StartTime
1232      type(ESMF_Time), intent(out) :: StopTime
1233      type(ESMF_Time), intent(out) :: RefTime
1234      type(ESMF_Time), intent(out) :: CurrTime
1235      type(ESMF_Time), intent(out) :: PrevTime
1236      integer(ESMF_KIND_I8), intent(out) :: AdvanceCount
1237      type(ESMF_Alarm), dimension(MAX_ALARMS), intent(out) :: AlarmList
1238      integer, intent(out), optional :: rc
1239   
1240! !DESCRIPTION:
1241!     Save an {\tt ESMF\_Clock}
1242!     
1243!     The arguments are:
1244!     \begin{description}
1245!     \item[clock]
1246!          The object instance to save
1247!     \item[TimeStep]
1248!          The {\tt ESMF\_Clock}'s time step interval
1249!     \item[StartTime]
1250!          The {\tt ESMF\_Clock}'s starting time
1251!     \item[StopTime]
1252!          The {\tt ESMF\_Clock}'s stopping time
1253!     \item[RefTime]
1254!          The {\tt ESMF\_Clock}'s reference time
1255!     \item[CurrTime]
1256!          The {\tt ESMF\_Clock}'s current time
1257!     \item[PrevTime]
1258!          The {\tt ESMF\_Clock}'s previous time
1259!     \item[AdvanceCount]
1260!          The number of times the {\tt ESMF\_Clock} has been advanced
1261!     \item[AlarmList]
1262!          The {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list
1263!     \item[{[rc]}]
1264!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1265!     \end{description}
1266!     
1267! !REQUIREMENTS:
1268!EOP
1269      CALL wrf_error_fatal( 'ESMF_ClockWrite not supported' )
1270      end subroutine ESMF_ClockWrite
1271
1272!------------------------------------------------------------------------------
1273!BOP
1274! !IROUTINE:  ESMF_ClockValidate - Validate a Clock's properties
1275
1276! !INTERFACE:
1277      subroutine ESMF_ClockValidate(clock, opts, rc)
1278
1279! !ARGUMENTS:
1280      type(ESMF_Clock), intent(in) :: clock
1281      character (len=*), intent(in), optional :: opts
1282      integer, intent(out), optional :: rc
1283
1284! !DESCRIPTION:
1285!     Perform a validation check on an {\tt ESMF\_Clock}'s properties
1286!
1287!     The arguments are: 
1288!     \begin{description}
1289!     \item[clock]
1290!          {\tt ESMF\_Clock} to validate
1291!     \item[{[opts]}]
1292!          Validate options
1293!     \item[{[rc]}]
1294!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1295!     \end{description}
1296!
1297! !REQUIREMENTS:
1298!     TMGn.n.n
1299!EOP
1300      CALL wrf_error_fatal( 'ESMF_ClockValidate not supported' )
1301      end subroutine ESMF_ClockValidate
1302
1303!------------------------------------------------------------------------------
1304!BOP
1305! !IROUTINE:  ESMF_ClockPrint - Print out a Clock's properties
1306
1307! !INTERFACE:
1308      subroutine ESMF_ClockPrint(clock, opts, rc)
1309
1310! !ARGUMENTS:
1311      type(ESMF_Clock), intent(in) :: clock
1312      character (len=*), intent(in), optional :: opts
1313      integer, intent(out), optional :: rc
1314
1315! !DESCRIPTION:
1316!     To support testing/debugging, print out an {\tt ESMF\_Clock}'s
1317!     properties.
1318!
1319!     The arguments are:
1320!     \begin{description}
1321!     \item[clock]
1322!          {\tt ESMF\_Clock} to print out
1323!     \item[{[opts]}]
1324!          Print options
1325!     \item[{[rc]}]
1326!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1327!     \end{description}
1328!
1329! !REQUIREMENTS:
1330!     TMGn.n.n
1331!EOP
1332      CALL wrf_error_fatal( 'ESMF_ClockPrint not supported' )
1333      end subroutine ESMF_ClockPrint
1334
1335!------------------------------------------------------------------------------
1336
1337      end module ESMF_ClockMod
Note: See TracBrowser for help on using the repository browser.