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