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

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

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 46.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! write(0,*)'ESMF_ClockAddAlarm ',clock%clockint%NumAlarms
787        clock%clockint%AlarmList(clock%clockint%NumAlarms) = Alarm
788      ENDIF
789   
790      end subroutine ESMF_ClockAddAlarm
791
792!------------------------------------------------------------------------------
793!BOP
794! !IROUTINE: ESMF_ClockGetAlarmList - Get a clock's alarm list
795
796! !INTERFACE:
797      subroutine ESMF_ClockGetAlarmList(clock, AlarmList, rc)
798
799! !ARGUMENTS:
800      type(ESMF_Clock), intent(in) :: clock
801      type(ESMF_Alarm), pointer :: AlarmList(:)
802      integer, intent(out), optional :: rc
803
804! !DESCRIPTION:
805!     Get an {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list     
806!   
807!     The arguments are:
808!     \begin{description}
809!     \item[clock]
810!          The object instance to get the {\tt ESMF\_Alarm} list from
811!     \item[AlarmList]
812!          The {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list
813!     \item[{[rc]}]
814!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
815!     \end{description}
816!   
817! !REQUIREMENTS:
818!     TMG4.3
819!EOP
820
821      AlarmList => clock%clockint%AlarmList
822      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
823
824      end subroutine ESMF_ClockGetAlarmList
825
826!------------------------------------------------------------------------------
827!BOP
828! !IROUTINE: ESMF_ClockGetNumAlarms - Get the number of alarms in a clock's alarm list
829
830! !INTERFACE:
831      subroutine ESMF_ClockGetNumAlarms(clock, NumAlarms, rc)
832
833! !ARGUMENTS:
834      type(ESMF_Clock), intent(in) :: clock
835      integer, intent(out) :: NumAlarms
836      integer, intent(out), optional :: rc
837
838! !DESCRIPTION:
839!     Get the number of {\tt ESMF\_Alarm}s in an {\tt ESMF\_Clock}'s
840!       {\tt ESMF\_Alarm} list     
841!   
842!     The arguments are:
843!     \begin{description}
844!     \item[clock]
845!          The object instance to get the number of {\tt ESMF\_Alarm}s from
846!     \item[NumAlarms]
847!          The number of {\tt ESMF\_Alarm}s in the {\tt ESMF\_Clock}'s
848!            {\tt ESMF\_Alarm} list
849!     \item[{[rc]}]
850!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
851!     \end{description}
852!   
853! !REQUIREMENTS:
854!     TMG4.3
855!EOP
856
857      NumAlarms = clock%clockint%NumAlarms
858      IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
859   
860      end subroutine ESMF_ClockGetNumAlarms
861
862!------------------------------------------------------------------------------
863!BOP
864! !IROUTINE: ESMF_ClockSyncToWallClock - Set clock's current time to wall clock time
865
866! !INTERFACE:
867      subroutine ESMF_ClockSyncToWallClock(clock, rc)
868
869! !ARGUMENTS:
870      type(ESMF_Clock), intent(inout) :: clock
871      integer, intent(out), optional :: rc
872   
873! !DESCRIPTION:
874!     Set an {\tt ESMF\_Clock}'s current time to wall clock time     
875!   
876!     The arguments are:
877!     \begin{description}
878!     \item[clock]
879!          The object instance to synchronize to wall clock time
880!     \item[{[rc]}]
881!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
882!     \end{description}
883!   
884! !REQUIREMENTS:
885!     TMG3.4.5
886!EOP
887      CALL wrf_error_fatal( 'ESMF_ClockSyncToWallClock not supported' )
888      end subroutine ESMF_ClockSyncToWallClock
889
890!------------------------------------------------------------------------------
891!BOP
892! !IROUTINE: ESMF_ClockAdvance - Advance a clock's current time by one time step
893
894! !INTERFACE:
895      subroutine ESMF_ClockAdvance(clock, RingingAlarmList, &
896                                   NumRingingAlarms, rc)
897
898use esmf_timemod
899
900! !ARGUMENTS:
901      type(ESMF_Clock), intent(inout) :: clock
902      type(ESMF_Alarm), dimension(MAX_ALARMS), intent(out), optional :: &
903                                        RingingAlarmList
904      integer, intent(out), optional :: NumRingingAlarms
905      integer, intent(out), optional :: rc
906! Local
907      logical pred1, pred2, pred3
908      integer i, n
909      type(ESMF_Alarm) :: alarm
910      logical :: positive_timestep
911!   
912! !DESCRIPTION:
913!     Advance an {\tt ESMF\_Clock}'s current time by one time step
914
915!     The arguments are:
916!     \begin{description}
917!     \item[clock]
918!          The object instance to advance
919!     \item[{[RingingAlarmList]}]
920!          Return a list of any ringing alarms after the time step
921!     \item[{[NumRingingAlarms]}]
922!          The number of ringing alarms returned
923!     \item[{[rc]}]
924!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
925!     \end{description}
926
927! !REQUIREMENTS:
928!     TMG3.4.1
929!EOP
930! hack for bug in PGI 5.1-x
931!      clock%clockint%CurrTime = clock%clockint%CurrTime + &
932!                                clock%clockint%TimeStep
933      clock%clockint%CurrTime = ESMF_TimeInc( clock%clockint%CurrTime, &
934                                              clock%clockint%TimeStep )
935      positive_timestep = ESMF_TimeIntervalIsPositive( clock%clockint%TimeStep )
936
937      IF ( Present(NumRingingAlarms) ) NumRingingAlarms = 0
938      clock%clockint%AdvanceCount = clock%clockint%AdvanceCount + 1
939      DO i = 1, MAX_ALARMS
940        alarm = clock%clockint%AlarmList(i)
941        ! TBH:  This is really dangerous.  We need to be able to NULLIFY
942        ! TBH:  alarmint at compile-time (F95 synax) to make this safe. 
943!$$$TBH:  see if F95 compile-time pointer-nullification is supported by all
944!$$$TBH:  compilers we support
945        IF ( ASSOCIATED( alarm%alarmint ) ) THEN
946          IF ( alarm%alarmint%Enabled ) THEN
947            IF ( alarm%alarmint%RingIntervalSet ) THEN
948              pred1 = .FALSE. ; pred2 = .FALSE. ; pred3 = .FALSE.
949              ! alarm cannot ring if clock has passed the alarms stop time
950              IF ( alarm%alarmint%StopTimeSet ) THEN
951                IF ( positive_timestep ) THEN
952! hack for bug in PGI 5.1-x
953!                  PRED1 = clock%clockint%CurrTime > alarm%alarmint%StopTime
954                  PRED1 = ESMF_TimeGT( clock%clockint%CurrTime, &
955                                       alarm%alarmint%StopTime )
956                ELSE
957                  ! in this case time step is negative and stop time is
958                  ! less than start time
959!                  PRED1 = clock%clockint%CurrTime < alarm%alarmint%StopTime
960                  PRED1 = ESMF_TimeLT( clock%clockint%CurrTime, &
961                                       alarm%alarmint%StopTime )
962                ENDIF
963              ENDIF
964              ! one-shot alarm:  check for ring time
965! TBH:  Need to remove duplicated code.  Need to enforce only one of
966! TBH:  alarm%alarmint%RingTimeSet or alarm%alarmint%RingIntervalSet ever
967! TBH:  being .TRUE. and simplify the logic.  Also, the simpler
968! TBH:  implementation in the duplicated code below should be sufficient. 
969              IF ( alarm%alarmint%RingTimeSet ) THEN
970                IF ( positive_timestep ) THEN
971! hack for bug in PGI 5.1-x
972!                   PRED2 = ( alarm%alarmint%RingTime <= clock%clockint%CurrTime     &
973!                          .AND. clock%clockint%CurrTime < alarm%alarmint%RingTime + &
974!                                clock%clockint%TimeStep )
975                   PRED2 = ( ESMF_TimeLE( alarm%alarmint%RingTime,       &
976                                          clock%clockint%CurrTime )      &
977                             .AND. ESMF_TimeLT( clock%clockint%CurrTime, &
978                               ESMF_TimeInc( alarm%alarmint%RingTime,    &
979                                             clock%clockint%TimeStep ) ) )
980                ELSE
981                  ! in this case time step is negative and stop time is
982                  ! less than start time
983! hack for bug in PGI 5.1-x
984!                   PRED2 = ( alarm%alarmint%RingTime >= clock%clockint%CurrTime     &
985!                          .AND. clock%clockint%CurrTime > alarm%alarmint%RingTime + &
986!                                clock%clockint%TimeStep )
987                   PRED2 = ( ESMF_TimeGE( alarm%alarmint%RingTime,       &
988                                          clock%clockint%CurrTime )      &
989                             .AND. ESMF_TimeGT( clock%clockint%CurrTime, &
990                               ESMF_TimeInc( alarm%alarmint%RingTime,    &
991                                             clock%clockint%TimeStep ) ) )
992                ENDIF
993              ENDIF
994              ! repeating alarm:  check for ring interval
995              IF ( alarm%alarmint%RingIntervalSet ) THEN
996                IF ( positive_timestep ) THEN
997! hack for bug in PGI 5.1-x
998!                   PRED3 = ( alarm%alarmint%PrevRingTime + alarm%alarmint%RingInterval <= &
999!                             clock%clockint%CurrTime )
1000
1001                   PRED3 = ( ESMF_TimeLE( ESMF_TimeInc(                  &
1002                                          alarm%alarmint%PrevRingTime,   &
1003                                          alarm%alarmint%RingInterval ), &
1004                             clock%clockint%CurrTime ) )
1005                ELSE
1006                  ! in this case time step is negative and stop time is
1007                  ! less than start time
1008                  ! ring interval must always be positive
1009! hack for bug in PGI 5.1-x
1010!                   PRED3 = ( alarm%alarmint%PrevRingTime - alarm%alarmint%RingInterval >= &
1011!                             clock%clockint%CurrTime )
1012
1013                   PRED3 = ( ESMF_TimeGE( ESMF_TimeDec(                  &
1014                                          alarm%alarmint%PrevRingTime,   &
1015                                          alarm%alarmint%RingInterval ), &
1016                             clock%clockint%CurrTime ) )
1017                ENDIF
1018              ENDIF
1019              IF ( (.NOT. pred1) .AND. pred2 ) THEN
1020                 alarm%alarmint%Ringing = .TRUE.
1021                 alarm%alarmint%PrevRingTime = clock%clockint%CurrTime
1022                 alarm%alarmint%RingTimeSet = .FALSE.  !it is a one time alarm, it rang, now let it resort to interval
1023                 IF ( PRESENT( RingingAlarmList ) .AND. &
1024                      PRESENT ( NumRingingAlarms ) ) THEN
1025                   NumRingingAlarms = NumRingingAlarms + 1
1026                   RingingAlarmList( NumRingingAlarms ) = alarm
1027                 ENDIF
1028              ELSE IF ( (.NOT. pred1) .AND. pred3 ) THEN
1029                 alarm%alarmint%Ringing = .TRUE.
1030                 IF ( positive_timestep ) THEN
1031! hack for bug in PGI 5.1-x
1032!                   IF ( PRED3) alarm%alarmint%PrevRingTime = alarm%alarmint%PrevRingTime + &
1033!                                                    alarm%alarmint%RingInterval
1034                   IF ( PRED3 )                                   &
1035                     alarm%alarmint%PrevRingTime =                &
1036                       ESMF_TimeInc( alarm%alarmint%PrevRingTime, &
1037                                     alarm%alarmint%RingInterval )
1038                 ELSE
1039                   ! in this case time step is negative and stop time is
1040                   ! less than start time
1041                   ! ring interval must always be positive
1042! hack for bug in PGI 5.1-x
1043!                   IF ( PRED3) alarm%alarmint%PrevRingTime = alarm%alarmint%PrevRingTime - &
1044!                                                    alarm%alarmint%RingInterval
1045                   IF ( PRED3 )                                   &
1046                     alarm%alarmint%PrevRingTime =                &
1047                       ESMF_TimeDec( alarm%alarmint%PrevRingTime, &
1048                                     alarm%alarmint%RingInterval )
1049                 ENDIF
1050                 IF ( PRESENT( RingingAlarmList ) .AND. &
1051                      PRESENT ( NumRingingAlarms ) ) THEN
1052                   NumRingingAlarms = NumRingingAlarms + 1
1053                   RingingAlarmList( NumRingingAlarms ) = alarm
1054                 ENDIF
1055              ENDIF
1056            ELSE IF ( alarm%alarmint%RingTimeSet ) THEN
1057! TBH:  Need to remove duplicated code.  Need to enforce only one of
1058! TBH:  alarm%alarmint%RingTimeSet or alarm%alarmint%RingIntervalSet ever
1059! TBH:  being .TRUE. and simplify the logic.  Also, the simpler
1060! TBH:  implementation in here should be sufficient. 
1061              IF ( positive_timestep ) THEN
1062! hack for bug in PGI 5.1-x
1063!                IF ( alarm%alarmint%RingTime <= clock%clockint%CurrTime ) THEN
1064                IF ( ESMF_TimeLE( alarm%alarmint%RingTime, &
1065                                  clock%clockint%CurrTime ) ) THEN
1066                   alarm%alarmint%RingTimeSet = .FALSE.  !it is a one time alarm, it rang, now let it resort to interval
1067                   alarm%alarmint%Ringing = .TRUE.
1068                   alarm%alarmint%PrevRingTime = clock%clockint%CurrTime
1069                   IF ( PRESENT( RingingAlarmList ) .AND. &
1070                        PRESENT ( NumRingingAlarms ) ) THEN
1071                     NumRingingAlarms = NumRingingAlarms + 1
1072                     RingingAlarmList( NumRingingAlarms ) = alarm
1073                   ENDIF
1074                ENDIF
1075              ELSE
1076                ! in this case time step is negative and stop time is
1077                ! less than start time
1078! hack for bug in PGI 5.1-x
1079!                IF ( alarm%alarmint%RingTime >= clock%clockint%CurrTime ) THEN
1080                IF ( ESMF_TimeGE( alarm%alarmint%RingTime, &
1081                                  clock%clockint%CurrTime ) ) THEN
1082                   alarm%alarmint%RingTimeSet = .FALSE.  !it is a one time alarm, it rang, now let it resort to interval
1083                   alarm%alarmint%Ringing = .TRUE.
1084                   alarm%alarmint%PrevRingTime = clock%clockint%CurrTime
1085                   IF ( PRESENT( RingingAlarmList ) .AND. &
1086                        PRESENT ( NumRingingAlarms ) ) THEN
1087                     NumRingingAlarms = NumRingingAlarms + 1
1088                     RingingAlarmList( NumRingingAlarms ) = alarm
1089                   ENDIF
1090                ENDIF
1091              ENDIF
1092            ENDIF
1093            IF ( alarm%alarmint%StopTimeSet ) THEN
1094! TBH:  what is this for??? 
1095            ENDIF
1096          ENDIF
1097        ENDIF
1098        clock%clockint%AlarmList(i) = alarm
1099      ENDDO
1100      IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
1101   
1102      end subroutine ESMF_ClockAdvance
1103
1104!------------------------------------------------------------------------------
1105!BOP
1106! !IROUTINE: ESMF_ClockStopTimeDisable - NOOP for compatibility with ESMF 2.1.0+
1107
1108! !INTERFACE:
1109      subroutine ESMF_ClockStopTimeDisable(clock, rc)
1110!
1111! !ARGUMENTS:
1112      type(ESMF_Clock), intent(in) :: clock
1113      integer, intent(out), optional :: rc
1114
1115      rc = ESMF_SUCCESS
1116
1117      end subroutine ESMF_ClockStopTimeDisable
1118
1119!------------------------------------------------------------------------------
1120!BOP
1121! !IROUTINE: ESMF_ClockIsStopTime - Has the clock reached its stop time ?
1122
1123! !INTERFACE:
1124      function ESMF_ClockIsStopTime(clock, rc)
1125!
1126! !RETURN VALUE:
1127      logical :: ESMF_ClockIsStopTime
1128
1129! !ARGUMENTS:
1130      type(ESMF_Clock), intent(in) :: clock
1131      integer, intent(out), optional :: rc
1132      logical :: positive_timestep
1133
1134! !DESCRIPTION:
1135!     Return true if {\tt ESMF\_Clock} has reached its stop time, false
1136!     otherwise     
1137!
1138!     The arguments are:
1139!     \begin{description}
1140!     \item[clock]
1141!          The object instance to check
1142!     \item[{[rc]}]
1143!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1144!     \end{description}
1145
1146! !REQUIREMENTS:
1147!     TMG3.5.6
1148!EOP
1149
1150      positive_timestep = ESMF_TimeIntervalIsPositive( clock%clockint%TimeStep )
1151      IF ( positive_timestep ) THEN
1152! hack for bug in PGI 5.1-x
1153!        if ( clock%clockint%CurrTime .GE. clock%clockint%StopTime ) THEN
1154        if ( ESMF_TimeGE( clock%clockint%CurrTime, &
1155                          clock%clockint%StopTime ) ) THEN
1156          ESMF_ClockIsStopTime = .TRUE.
1157        else
1158          ESMF_ClockIsStopTime = .FALSE.
1159        endif
1160      ELSE
1161! hack for bug in PGI 5.1-x
1162!        if ( clock%clockint%CurrTime .LE. clock%clockint%StopTime ) THEN
1163        if ( ESMF_TimeLE( clock%clockint%CurrTime, &
1164                          clock%clockint%StopTime ) ) THEN
1165          ESMF_ClockIsStopTime = .TRUE.
1166        else
1167          ESMF_ClockIsStopTime = .FALSE.
1168        endif
1169      ENDIF
1170      IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
1171   
1172      end function ESMF_ClockIsStopTime
1173
1174!------------------------------------------------------------------------------
1175!
1176! This section defines the overridden Read, Write, Validate and Print methods
1177! from the ESMF_Base class
1178!
1179!------------------------------------------------------------------------------
1180!BOP
1181! !IROUTINE: ESMF_ClockRead - Restores a clock
1182
1183! !INTERFACE:
1184      subroutine ESMF_ClockRead(clock, TimeStep, StartTime, StopTime, &
1185                                RefTime, CurrTime, PrevTime, AdvanceCount, &
1186                                AlarmList, rc)
1187
1188! !ARGUMENTS:
1189      type(ESMF_Clock), intent(out) :: clock
1190      type(ESMF_TimeInterval), intent(in) :: TimeStep
1191      type(ESMF_Time), intent(in) :: StartTime
1192      type(ESMF_Time), intent(in) :: StopTime
1193      type(ESMF_Time), intent(in) :: RefTime
1194      type(ESMF_Time), intent(in) :: CurrTime
1195      type(ESMF_Time), intent(in) :: PrevTime
1196      integer(ESMF_KIND_I8), intent(in) :: AdvanceCount
1197      type(ESMF_Alarm), dimension(MAX_ALARMS), intent(in) :: AlarmList
1198      integer, intent(out), optional :: rc
1199   
1200! !DESCRIPTION:
1201!     Restore an {\tt ESMF\_Clock}
1202!     
1203!     The arguments are:
1204!     \begin{description}
1205!     \item[clock]
1206!          The object instance to restore
1207!     \item[TimeStep]
1208!          The {\tt ESMF\_Clock}'s time step interval
1209!     \item[StartTime]
1210!          The {\tt ESMF\_Clock}'s starting time
1211!     \item[StopTime]
1212!          The {\tt ESMF\_Clock}'s stopping time
1213!     \item[RefTime]
1214!          The {\tt ESMF\_Clock}'s reference time
1215!     \item[CurrTime]
1216!          The {\tt ESMF\_Clock}'s current time
1217!     \item[PrevTime]
1218!          The {\tt ESMF\_Clock}'s previous time
1219!     \item[AdvanceCount]
1220!          The number of times the {\tt ESMF\_Clock} has been advanced
1221!     \item[AlarmList]
1222!          The {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list
1223!     \item[{[rc]}]
1224!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1225!     \end{description}
1226!     
1227! !REQUIREMENTS:
1228!EOP
1229      CALL wrf_error_fatal( 'ESMF_ClockRead not supported' )
1230      end subroutine ESMF_ClockRead
1231
1232!------------------------------------------------------------------------------
1233!BOP
1234! !IROUTINE: ESMF_ClockWrite - Saves a clock
1235
1236! !INTERFACE:
1237      subroutine ESMF_ClockWrite(clock, TimeStep, StartTime, StopTime, &
1238                            RefTime, CurrTime, PrevTime, AdvanceCount, &
1239                            AlarmList, rc)
1240
1241! !ARGUMENTS:
1242      type(ESMF_Clock), intent(in) :: clock
1243      type(ESMF_TimeInterval), intent(out) :: TimeStep
1244      type(ESMF_Time), intent(out) :: StartTime
1245      type(ESMF_Time), intent(out) :: StopTime
1246      type(ESMF_Time), intent(out) :: RefTime
1247      type(ESMF_Time), intent(out) :: CurrTime
1248      type(ESMF_Time), intent(out) :: PrevTime
1249      integer(ESMF_KIND_I8), intent(out) :: AdvanceCount
1250      type(ESMF_Alarm), dimension(MAX_ALARMS), intent(out) :: AlarmList
1251      integer, intent(out), optional :: rc
1252   
1253! !DESCRIPTION:
1254!     Save an {\tt ESMF\_Clock}
1255!     
1256!     The arguments are:
1257!     \begin{description}
1258!     \item[clock]
1259!          The object instance to save
1260!     \item[TimeStep]
1261!          The {\tt ESMF\_Clock}'s time step interval
1262!     \item[StartTime]
1263!          The {\tt ESMF\_Clock}'s starting time
1264!     \item[StopTime]
1265!          The {\tt ESMF\_Clock}'s stopping time
1266!     \item[RefTime]
1267!          The {\tt ESMF\_Clock}'s reference time
1268!     \item[CurrTime]
1269!          The {\tt ESMF\_Clock}'s current time
1270!     \item[PrevTime]
1271!          The {\tt ESMF\_Clock}'s previous time
1272!     \item[AdvanceCount]
1273!          The number of times the {\tt ESMF\_Clock} has been advanced
1274!     \item[AlarmList]
1275!          The {\tt ESMF\_Clock}'s {\tt ESMF\_Alarm} list
1276!     \item[{[rc]}]
1277!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1278!     \end{description}
1279!     
1280! !REQUIREMENTS:
1281!EOP
1282      CALL wrf_error_fatal( 'ESMF_ClockWrite not supported' )
1283      end subroutine ESMF_ClockWrite
1284
1285!------------------------------------------------------------------------------
1286!BOP
1287! !IROUTINE:  ESMF_ClockValidate - Validate a Clock's properties
1288
1289! !INTERFACE:
1290      subroutine ESMF_ClockValidate(clock, opts, rc)
1291
1292! !ARGUMENTS:
1293      type(ESMF_Clock), intent(in) :: clock
1294      character (len=*), intent(in), optional :: opts
1295      integer, intent(out), optional :: rc
1296
1297! !DESCRIPTION:
1298!     Perform a validation check on an {\tt ESMF\_Clock}'s properties
1299!
1300!     The arguments are: 
1301!     \begin{description}
1302!     \item[clock]
1303!          {\tt ESMF\_Clock} to validate
1304!     \item[{[opts]}]
1305!          Validate options
1306!     \item[{[rc]}]
1307!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1308!     \end{description}
1309!
1310! !REQUIREMENTS:
1311!     TMGn.n.n
1312!EOP
1313      CALL wrf_error_fatal( 'ESMF_ClockValidate not supported' )
1314      end subroutine ESMF_ClockValidate
1315
1316!------------------------------------------------------------------------------
1317!BOP
1318! !IROUTINE:  ESMF_ClockPrint - Print out a Clock's properties
1319
1320! !INTERFACE:
1321      subroutine ESMF_ClockPrint(clock, opts, rc)
1322
1323! !ARGUMENTS:
1324      type(ESMF_Clock), intent(in) :: clock
1325      character (len=*), intent(in), optional :: opts
1326      integer, intent(out), optional :: rc
1327
1328! !DESCRIPTION:
1329!     To support testing/debugging, print out an {\tt ESMF\_Clock}'s
1330!     properties.
1331!
1332!     The arguments are:
1333!     \begin{description}
1334!     \item[clock]
1335!          {\tt ESMF\_Clock} to print out
1336!     \item[{[opts]}]
1337!          Print options
1338!     \item[{[rc]}]
1339!          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1340!     \end{description}
1341!
1342! !REQUIREMENTS:
1343!     TMGn.n.n
1344!EOP
1345      CALL wrf_error_fatal( 'ESMF_ClockPrint not supported' )
1346      end subroutine ESMF_ClockPrint
1347
1348!------------------------------------------------------------------------------
1349
1350      end module ESMF_ClockMod
Note: See TracBrowser for help on using the repository browser.