r5152 | xinzhang | 2011-09-26 21:04:33 -0700 (Mon, 26 Sep 2011) | 3 lines
[wrffire.git] / wrfv2_fire / external / esmf_time_f90 / ESMF_TimeInterval.F90
blob95d4edc5a12118d71f6e592be772cc38e049e155
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.
10 !==============================================================================
12 !     ESMF TimeInterval Module
13       module ESMF_TimeIntervalMod
15 !==============================================================================
17 ! This file contains the TimeInterval class definition and all TimeInterval
18 ! class methods.
20 !------------------------------------------------------------------------------
21 ! INCLUDES
22 #include <ESMF_TimeMgr.inc>
24 !===============================================================================
25 !BOPI
26 ! !MODULE: ESMF_TimeIntervalMod
28 ! !DESCRIPTION:
29 ! Part of Time Manager F90 API wrapper of C++ implemenation
31 ! Defines F90 wrapper entry points for corresponding
32 ! C++ implementaion of class {\tt ESMC\_TimeInterval}
34 ! See {\tt ../include/ESMC\_TimeInterval.h} for complete description
36 !------------------------------------------------------------------------------
37 ! !USES:
38       ! inherit from ESMF base class
39       use ESMF_BaseMod
41       ! inherit from base time class
42       use ESMF_BaseTimeMod
44       ! associated derived types
45       use ESMF_FractionMod, only : ESMF_Fraction
46       use ESMF_CalendarMod
48       implicit none
50 !------------------------------------------------------------------------------
51 ! !PRIVATE TYPES:
52       private
53 !------------------------------------------------------------------------------
54 !     ! ESMF_TimeInterval
56 !     ! F90 class type to match C++ TimeInterval class in size only;
57 !     !  all dereferencing within class is performed by C++ implementation
59       type ESMF_TimeInterval
60         ! time interval is expressed as basetime
61         type(ESMF_BaseTime) :: basetime  ! inherit base class
62         ! Relative year and month fields support monthly or yearly time 
63         ! intervals.  Many operations are undefined when these fields are 
64         ! non-zero!  
65         INTEGER :: YR                    ! relative year
66    !jm Month has no meaning for an interval; get rid of it, 20100319
67    !     INTEGER :: MM                    ! relative month
68       end type
70 !------------------------------------------------------------------------------
71 ! !PUBLIC TYPES:
72       public ESMF_TimeInterval
73 !------------------------------------------------------------------------------
75 ! !PUBLIC MEMBER FUNCTIONS:
76       public ESMF_TimeIntervalGet
77       public ESMF_TimeIntervalSet
78       public ESMFold_TimeIntervalGetString
79       public ESMF_TimeIntervalAbsValue
80       public ESMF_TimeIntervalNegAbsValue
82 ! Required inherited and overridden ESMF_Base class methods
84 !!!!!!!!! added 20051012, JM
85 !      public WRFADDITION_TimeIntervalDIVQuot 
86 !!!!!!!!! renamed to simplify testing 20060320, TH
87       public ESMF_TimeIntervalDIVQuot 
89       ! This convenience routine is only used by other modules in 
90       ! esmf_time_f90.  
91       public ESMF_TimeIntervalIsPositive
94 ! !PRIVATE MEMBER FUNCTIONS:
96 ! overloaded operator functions
98       public operator(/)
99       private ESMF_TimeIntervalQuotI
101       public operator(*)
102       private ESMF_TimeIntervalProdI
104 ! Inherited and overloaded from ESMF_BaseTime
106       public operator(+)
107       private ESMF_TimeIntervalSum
109       public operator(-)
110       private ESMF_TimeIntervalDiff
112       public operator(.EQ.)
113       private ESMF_TimeIntervalEQ
115       public operator(.NE.)
116       private ESMF_TimeIntervalNE
118       public operator(.LT.)
119       private ESMF_TimeIntervalLT
121       public operator(.GT.)
122       private ESMF_TimeIntervalGT
124       public operator(.LE.)
125       private ESMF_TimeIntervalLE
127       public operator(.GE.)
128       private ESMF_TimeIntervalGE
129 !EOPI
131 !==============================================================================
133 ! INTERFACE BLOCKS
135 !==============================================================================
136 !BOP
137 ! !INTERFACE:
138       interface operator(*)
140 ! !PRIVATE MEMBER FUNCTIONS:
141       module procedure ESMF_TimeIntervalProdI
143 ! !DESCRIPTION:
144 !     This interface overloads the * operator for the {\tt ESMF\_TimeInterval}
145 !     class
147 !EOP
148       end interface
150 !------------------------------------------------------------------------------
151 !BOP
152 ! !INTERFACE:
153       interface operator(/)
155 ! !PRIVATE MEMBER FUNCTIONS:
156       module procedure ESMF_TimeIntervalQuotI
158 ! !DESCRIPTION:
159 !     This interface overloads the / operator for the
160 !     {\tt ESMF\_TimeInterval} class
162 !EOP
163       end interface
165 !------------------------------------------------------------------------------
166 !BOP
167 ! !INTERFACE:
168       interface operator(+)
170 ! !PRIVATE MEMBER FUNCTIONS:
171       module procedure ESMF_TimeIntervalSum
173 ! !DESCRIPTION:
174 !     This interface overloads the + operator for the
175 !     {\tt ESMF\_TimeInterval} class
177 !EOP
178       end interface
180 !------------------------------------------------------------------------------
181 !BOP
182 ! !INTERFACE:
183       interface operator(-)
185 ! !PRIVATE MEMBER FUNCTIONS:
186       module procedure ESMF_TimeIntervalDiff
188 ! !DESCRIPTION:
189 !     This interface overloads the - operator for the
190 !     {\tt ESMF\_TimeInterval} class
192 !EOP
193       end interface
195 !------------------------------------------------------------------------------
196 !BOP
197 ! !INTERFACE:
198       interface operator(.EQ.)
200 ! !PRIVATE MEMBER FUNCTIONS:
201       module procedure ESMF_TimeIntervalEQ
203 ! !DESCRIPTION:
204 !     This interface overloads the .EQ. operator for the
205 !     {\tt ESMF\_TimeInterval} class
207 !EOP
208       end interface
210 !------------------------------------------------------------------------------
211 !BOP
212 ! !INTERFACE:
213       interface operator(.NE.)
215 ! !PRIVATE MEMBER FUNCTIONS:
216       module procedure ESMF_TimeIntervalNE
218 ! !DESCRIPTION:
219 !     This interface overloads the .NE. operator for the
220 !     {\tt ESMF\_TimeInterval} class
222 !EOP
223       end interface
225 !------------------------------------------------------------------------------
226 !BOP
227 ! !INTERFACE:
228       interface operator(.LT.)
230 ! !PRIVATE MEMBER FUNCTIONS:
231       module procedure ESMF_TimeIntervalLT
233 ! !DESCRIPTION:
234 !     This interface overloads the .LT. operator for the
235 !     {\tt ESMF\_TimeInterval} class
237 !EOP
238       end interface
240 !------------------------------------------------------------------------------
241 !BOP
242 ! !INTERFACE:
243       interface operator(.GT.)
245 ! !PRIVATE MEMBER FUNCTIONS:
246       module procedure ESMF_TimeIntervalGT
248 ! !DESCRIPTION:
249 !     This interface overloads the .GT. operator for the
250 !     {\tt ESMF\_TimeInterval} class
252 !EOP
253       end interface
255 !------------------------------------------------------------------------------
256 !BOP
257 ! !INTERFACE:
258       interface operator(.LE.)
260 ! !PRIVATE MEMBER FUNCTIONS:
261       module procedure ESMF_TimeIntervalLE
263 ! !DESCRIPTION:
264 !     This interface overloads the .LE. operator for the
265 !     {\tt ESMF\_TimeInterval} class
267 !EOP
268       end interface
270 !------------------------------------------------------------------------------
271 !BOP
272 ! !INTERFACE:
273       interface operator(.GE.)
275 ! !PRIVATE MEMBER FUNCTIONS:
276       module procedure ESMF_TimeIntervalGE
278 ! !DESCRIPTION:
279 !     This interface overloads the .GE. operator for the
280 !     {\tt ESMF\_TimeInterval} class
282 !EOP
283       end interface
285 !------------------------------------------------------------------------------
287 !==============================================================================
289       contains
291 !==============================================================================
293 ! Generic Get/Set routines which use F90 optional arguments
295 !------------------------------------------------------------------------------
296 !BOP
297 ! !IROUTINE: ESMF_TimeIntervalGet - Get value in user-specified units
299 ! !INTERFACE:
300       subroutine ESMF_TimeIntervalGet(timeinterval, D, d_r8, S, S_i8, Sn, Sd, &
301                                       TimeString, rc )
303 ! !ARGUMENTS:
304       type(ESMF_TimeInterval), intent(in) :: timeinterval
305       integer, intent(out), optional :: D
306       real(ESMF_KIND_R8),     intent(out), optional :: d_r8
307       integer(ESMF_KIND_I8),  intent(out), optional :: S_i8
308       integer, intent(out), optional :: S
309       integer, intent(out), optional :: Sn
310       integer, intent(out), optional :: Sd
311       character*(*), optional, intent(out) :: TimeString
312       integer, intent(out), optional :: rc
315 ! !DESCRIPTION:
316 !     Get the value of the {\tt ESMF\_TimeInterval} in units specified by the
317 !     user via F90 optional arguments.
319 !     Time manager represents and manipulates time internally with integers 
320 !     to maintain precision.  Hence, user-specified floating point values are
321 !     converted internally from integers.
323 !     See {\tt ../include/ESMC\_BaseTime.h} and
324 !     {\tt ../include/ESMC\_TimeInterval.h} for complete description.
325 !     
326 !     The arguments are:
327 !     \begin{description}
328 !     \item[timeinterval]
329 !          The object instance to query
330 !     \item[{[YY]}]
331 !          Integer years (>= 32-bit)
332 !     \item[{[YYl]}]
333 !          Integer years (large, >= 64-bit)
334 !     \item[{[MO]}]
335 !          Integer months (>= 32-bit)
336 !     \item[{[MOl]}]
337 !          Integer months (large, >= 64-bit)
338 !     \item[{[D]}]
339 !          Integer days (>= 32-bit)
340 !     \item[{[Dl]}]
341 !          Integer days (large, >= 64-bit)
342 !     \item[{[H]}]
343 !          Integer hours
344 !     \item[{[M]}]
345 !          Integer minutes
346 !     \item[{[S]}]
347 !          Integer seconds (>= 32-bit)
348 !     \item[{[Sl]}]
349 !          Integer seconds (large, >= 64-bit)
350 !     \item[{[MS]}]
351 !          Integer milliseconds
352 !     \item[{[US]}]
353 !          Integer microseconds
354 !     \item[{[NS]}]
355 !          Integer nanoseconds
356 !     \item[{[d\_]}]
357 !          Double precision days
358 !     \item[{[h\_]}]
359 !          Double precision hours
360 !     \item[{[m\_]}]
361 !          Double precision minutes
362 !     \item[{[s\_]}]
363 !          Double precision seconds
364 !     \item[{[ms\_]}]
365 !          Double precision milliseconds
366 !     \item[{[us\_]}]
367 !          Double precision microseconds
368 !     \item[{[ns\_]}]
369 !          Double precision nanoseconds
370 !     \item[{[Sn]}]
371 !          Integer fractional seconds - numerator
372 !     \item[{[Sd]}]
373 !          Integer fractional seconds - denominator
374 !     \item[{[rc]}]
375 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
376 !     \end{description}
378 ! !REQUIREMENTS:
379 !     TMG1.1
381 ! Added argument to output double precision seconds, S_i8
382 ! William.Gustafson@pnl.gov; 9-May-2008
384 !EOP
385       INTEGER(ESMF_KIND_I8) :: seconds
386       INTEGER :: ierr
388       ierr = ESMF_SUCCESS
389       seconds = timeinterval%basetime%S
390       ! note that S is overwritten below (if present) if other args are also 
391       ! present
392       IF ( PRESENT(S) ) S = seconds
393       IF ( PRESENT(S_i8) ) S_i8 = seconds
394       IF ( PRESENT( D ) ) THEN
395         D = seconds / SECONDS_PER_DAY
396         IF ( PRESENT(S) )    S    = MOD( seconds, SECONDS_PER_DAY )
397         IF ( PRESENT(S_i8) ) S_i8 = MOD( seconds, SECONDS_PER_DAY )
398       ENDIF
399       IF ( PRESENT( d_r8 ) ) THEN
400         D_r8 = REAL( seconds, ESMF_KIND_R8 ) / &
401                REAL( SECONDS_PER_DAY, ESMF_KIND_R8 )
402         IF ( PRESENT(S) )    S    = MOD( seconds, SECONDS_PER_DAY )
403         IF ( PRESENT(S_i8) ) S_i8 = MOD( seconds, SECONDS_PER_DAY )
404       ENDIF
405       IF ( PRESENT(Sn) ) THEN
406         Sn = timeinterval%basetime%Sn
407       ENDIF
408       IF ( PRESENT(Sd) ) THEN
409         Sd = timeinterval%basetime%Sd
410       ENDIF
411       IF ( PRESENT( timeString ) ) THEN
412         CALL ESMFold_TimeIntervalGetString( timeinterval, timeString, rc=ierr )
413       ENDIF
414       IF ( PRESENT(rc) ) rc = ierr
415     
416       end subroutine ESMF_TimeIntervalGet
418 !------------------------------------------------------------------------------
419 !BOP
420 ! !IROUTINE: ESMF_TimeIntervalSet - Initialize via user-specified unit set
422 ! !INTERFACE:
423       subroutine ESMF_TimeIntervalSet(timeinterval, YY, YYl, MM, MOl, D, Dl, &
424                                       H, M, S, Sl, MS, US, NS, &
425                                       d_, h_, m_, s_, ms_, us_, ns_, &
426                                       Sn, Sd, rc)
428 ! !ARGUMENTS:
429       type(ESMF_TimeInterval), intent(out) :: timeinterval
430       integer, intent(in), optional :: YY
431       integer(ESMF_KIND_I8), intent(in), optional :: YYl
432       integer, intent(in), optional :: MM
433       integer(ESMF_KIND_I8), intent(in), optional :: MOl
434       integer, intent(in), optional :: D
435       integer(ESMF_KIND_I8), intent(in), optional :: Dl
436       integer, intent(in), optional :: H
437       integer, intent(in), optional :: M
438       integer, intent(in), optional :: S
439       integer(ESMF_KIND_I8), intent(in), optional :: Sl
440       integer, intent(in), optional :: MS
441       integer, intent(in), optional :: US
442       integer, intent(in), optional :: NS
443       double precision, intent(in), optional :: d_
444       double precision, intent(in), optional :: h_
445       double precision, intent(in), optional :: m_
446       double precision, intent(in), optional :: s_
447       double precision, intent(in), optional :: ms_
448       double precision, intent(in), optional :: us_
449       double precision, intent(in), optional :: ns_
450       integer, intent(in), optional :: Sn
451       integer, intent(in), optional :: Sd
452       integer, intent(out), optional :: rc
453       ! locals
454       INTEGER :: nfeb
456 ! !DESCRIPTION:
457 !     Set the value of the {\tt ESMF\_TimeInterval} in units specified by
458 !     the user via F90 optional arguments
460 !     Time manager represents and manipulates time internally with integers 
461 !     to maintain precision.  Hence, user-specified floating point values are
462 !     converted internally to integers.
464 !     See {\tt ../include/ESMC\_BaseTime.h} and
465 !     {\tt ../include/ESMC\_TimeInterval.h} for complete description.
467 !     The arguments are:
468 !     \begin{description}
469 !     \item[timeinterval]
470 !          The object instance to initialize
471 !     \item[{[YY]}]
472 !          Integer number of interval years (>= 32-bit)
473 !     \item[{[YYl]}]
474 !          Integer number of interval years (large, >= 64-bit)
475 !     \item[{[MM]}]
476 !          Integer number of interval months (>= 32-bit)
477 !     \item[{[MOl]}]
478 !          Integer number of interval months (large, >= 64-bit)
479 !     \item[{[D]}]
480 !          Integer number of interval days (>= 32-bit)
481 !     \item[{[Dl]}]
482 !          Integer number of interval days (large, >= 64-bit)
483 !     \item[{[H]}]
484 !          Integer hours
485 !     \item[{[M]}]
486 !          Integer minutes
487 !     \item[{[S]}]
488 !          Integer seconds (>= 32-bit)
489 !     \item[{[Sl]}]
490 !          Integer seconds (large, >= 64-bit)
491 !     \item[{[MS]}]
492 !          Integer milliseconds
493 !     \item[{[US]}]
494 !          Integer microseconds
495 !     \item[{[NS]}]
496 !          Integer nanoseconds
497 !     \item[{[d\_]}]
498 !          Double precision days
499 !     \item[{[h\_]}]
500 !          Double precision hours
501 !     \item[{[m\_]}]
502 !          Double precision minutes
503 !     \item[{[s\_]}]
504 !          Double precision seconds
505 !     \item[{[ms\_]}]
506 !          Double precision milliseconds
507 !     \item[{[us\_]}]
508 !          Double precision microseconds
509 !     \item[{[ns\_]}]
510 !          Double precision nanoseconds
511 !     \item[{[Sn]}]
512 !          Integer fractional seconds - numerator
513 !     \item[{[Sd]}]
514 !          Integer fractional seconds - denominator
515 !     \item[{[rc]}]
516 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
517 !     \end{description}
519 ! !REQUIREMENTS:
520 !     TMGn.n.n
521 !EOP
523       IF ( PRESENT(rc) ) rc = ESMF_FAILURE
524       ! note that YR and MM are relative
525       timeinterval%YR = 0
526       IF ( PRESENT( YY ) ) THEN
527         timeinterval%YR = YY
528       ENDIF
529 !jm      timeinterval%MM = 0
530 !jm      IF ( PRESENT( MM ) ) THEN
531 !jm        timeinterval%MM = MM
532 !jm      ENDIF
533 !jm      ! Rollover months to years
534 !jm      IF      ( abs(timeinterval%MM) .GE. MONTHS_PER_YEAR ) THEN
535 !jm        timeinterval%YR = timeinterval%YR + timeinterval%MM/MONTHS_PER_YEAR
536 !jm        timeinterval%MM = mod(timeinterval%MM,MONTHS_PER_YEAR)
537 !jm      ENDIF
539       timeinterval%basetime%S = 0
540       ! For 365-day calendar, immediately convert years to days since we know 
541       ! how to do it in this case.  
542 !$$$ replace this hack with something saner...
543       IF ( nfeb( 2004 ) == 28 ) THEN
544         timeinterval%basetime%S = timeinterval%basetime%S + &
545           ( 365_ESMF_KIND_I8 * &
546             INT( timeinterval%YR, ESMF_KIND_I8 ) * SECONDS_PER_DAY )
547         timeinterval%YR = 0
548       ENDIF
549       IF ( PRESENT( D ) ) THEN
550         timeinterval%basetime%S = timeinterval%basetime%S + &
551           ( SECONDS_PER_DAY * INT( D, ESMF_KIND_I8 ) )
552       ENDIF
553 !$$$ Push H,M,S,Sn,Sd,MS down into BaseTime constructor from EVERYWHERE
554 !$$$ and THEN add ESMF scaling behavior when other args are present...  
555       IF ( PRESENT( H ) ) THEN
556         timeinterval%basetime%S = timeinterval%basetime%S + &
557           ( SECONDS_PER_HOUR * INT( H, ESMF_KIND_I8 ) )
558       ENDIF
559       IF ( PRESENT( M ) ) THEN
560         timeinterval%basetime%S = timeinterval%basetime%S + &
561           ( SECONDS_PER_MINUTE * INT( M, ESMF_KIND_I8 ) )
562       ENDIF
563       IF ( PRESENT( S ) ) THEN
564         timeinterval%basetime%S = timeinterval%basetime%S + &
565           INT( S, ESMF_KIND_I8 )
566       ENDIF
567       IF ( PRESENT( Sn ) .AND. ( .NOT. PRESENT( Sd ) ) ) THEN
568         CALL wrf_error_fatal( &
569           "ESMF_TimeIntervalSet:  Must specify Sd if Sn is specified")
570       ENDIF
571       IF ( PRESENT( Sd ) .AND. PRESENT( MS ) ) THEN
572         CALL wrf_error_fatal( &
573           "ESMF_TimeIntervalSet:  Must not specify both Sd and MS")
574       ENDIF
575       timeinterval%basetime%Sn = 0
576       timeinterval%basetime%Sd = 0
577       IF ( PRESENT( MS ) ) THEN
578         timeinterval%basetime%Sn = MS
579         timeinterval%basetime%Sd = 1000_ESMF_KIND_I8
580       ELSE IF ( PRESENT( Sd ) ) THEN
581         timeinterval%basetime%Sd = Sd
582         IF ( PRESENT( Sn ) ) THEN
583           timeinterval%basetime%Sn = Sn
584         ENDIF
585       ENDIF
586       CALL normalize_timeint( timeinterval )
588       IF ( PRESENT(rc) ) rc = ESMF_SUCCESS
590       end subroutine ESMF_TimeIntervalSet
592 !------------------------------------------------------------------------------
593 !BOP
594 ! !IROUTINE:  ESMFold_TimeIntervalGetString - Get time interval value in string format
596 ! !INTERFACE:
597       subroutine ESMFold_TimeIntervalGetString(timeinterval, TimeString, rc)
599 ! !ARGUMENTS:
600       type(ESMF_TimeInterval), intent(in) :: timeinterval
601       character*(*),  intent(out) :: TimeString
602       integer, intent(out), optional :: rc
603       ! locals
604       integer :: signnormtimeint
605       LOGICAL :: negative
606       INTEGER(ESMF_KIND_I8) :: iS, iSn, iSd, H, M, S
607       character (len=1) :: signstr
609 ! !DESCRIPTION:
610 !     Convert {\tt ESMF\_TimeInterval}'s value into string format
612 !     The arguments are:
613 !     \begin{description}
614 !     \item[timeinterval]
615 !          The object instance to convert
616 !     \item[TimeString]
617 !          The string to return
618 !     \item[{[rc]}]
619 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
620 !     \end{description}
622 ! !REQUIREMENTS:
623 !     TMG1.5.9
624 !EOP
626 ! NOTE:  YR, MM, Sn, and Sd are not yet included in the returned string...  
627 !PRINT *,'DEBUG ESMFold_TimeIntervalGetString():  YR,MM,S,Sn,Sd = ', &
628 !        timeinterval%YR, &
629 !        timeinterval%MM, &
630 !        timeinterval%basetime%S, &
631 !        timeinterval%basetime%Sn, &
632 !        timeinterval%basetime%Sd
634       negative = ( signnormtimeint( timeInterval ) == -1 )
635       IF ( negative ) THEN
636         iS = -timeinterval%basetime%S
637         iSn = -timeinterval%basetime%Sn
638         signstr = '-'
639       ELSE
640         iS = timeinterval%basetime%S
641         iSn = timeinterval%basetime%Sn
642         signstr = ''
643       ENDIF 
644       iSd = timeinterval%basetime%Sd
646       H = mod( iS, SECONDS_PER_DAY ) / SECONDS_PER_HOUR
647       M = mod( iS, SECONDS_PER_HOUR) / SECONDS_PER_MINUTE
648       S = mod( iS, SECONDS_PER_MINUTE )
650 !$$$here...  need to print Sn and Sd when they are used ???
652       write(TimeString,FMT="(A,I10.10,'_',I3.3,':',I3.3,':',I3.3)") &
653         TRIM(signstr), ( iS / SECONDS_PER_DAY ), H, M, S
655 !write(0,*)'TimeIntervalGetString Sn ',timeinterval%basetime%Sn,' Sd ',timeinterval%basetime%Sd
657       rc = ESMF_SUCCESS
659       end subroutine ESMFold_TimeIntervalGetString
661 !------------------------------------------------------------------------------
662 !BOP
663 ! !IROUTINE:  ESMF_TimeIntervalAbsValue - Get the absolute value of a time interval
665 ! !INTERFACE:
666       function ESMF_TimeIntervalAbsValue(timeinterval)
668 ! !RETURN VALUE:
669       type(ESMF_TimeInterval) :: ESMF_TimeIntervalAbsValue
671 ! !ARGUMENTS:
672       type(ESMF_TimeInterval), intent(in) :: timeinterval
673 ! !LOCAL:
674       integer    :: rc
676 ! !DESCRIPTION:
677 !     Return a {\tt ESMF\_TimeInterval}'s absolute value.
679 !     The arguments are:
680 !     \begin{description}
681 !     \item[timeinterval]
682 !          The object instance to take the absolute value of.
683 !          Absolute value returned as value of function.
684 !     \end{description}
686 ! !REQUIREMENTS:
687 !     TMG1.5.8
688 !EOP
689       CALL timeintchecknormalized( timeinterval, 'ESMF_TimeIntervalAbsValue arg1' )
690       ESMF_TimeIntervalAbsValue = timeinterval
691 !$$$here...  move implementation into BaseTime
692       ESMF_TimeIntervalAbsValue%basetime%S  = &
693         abs(ESMF_TimeIntervalAbsValue%basetime%S)
694       ESMF_TimeIntervalAbsValue%basetime%Sn = &
695         abs(ESMF_TimeIntervalAbsValue%basetime%Sn )
697       end function ESMF_TimeIntervalAbsValue
699 !------------------------------------------------------------------------------
700 !BOP
701 ! !IROUTINE:  ESMF_TimeIntervalNegAbsValue - Get the negative absolute value of a time interval
703 ! !INTERFACE:
704       function ESMF_TimeIntervalNegAbsValue(timeinterval)
706 ! !RETURN VALUE:
707       type(ESMF_TimeInterval) :: ESMF_TimeIntervalNegAbsValue
709 ! !ARGUMENTS:
710       type(ESMF_TimeInterval), intent(in) :: timeinterval
711 ! !LOCAL:
712       integer    :: rc
714 ! !DESCRIPTION:
715 !     Return a {\tt ESMF\_TimeInterval}'s negative absolute value.
717 !     The arguments are:
718 !     \begin{description}
719 !     \item[timeinterval]
720 !          The object instance to take the negative absolute value of.
721 !          Negative absolute value returned as value of function.
722 !     \end{description}
724 ! !REQUIREMENTS:
725 !     TMG1.5.8
726 !EOP
727       CALL timeintchecknormalized( timeinterval, 'ESMF_TimeIntervalNegAbsValue arg1' )
728     
729       ESMF_TimeIntervalNegAbsValue = timeinterval
730 !$$$here...  move implementation into BaseTime
731       ESMF_TimeIntervalNegAbsValue%basetime%S  = &
732         -abs(ESMF_TimeIntervalNegAbsValue%basetime%S)
733       ESMF_TimeIntervalNegAbsValue%basetime%Sn = &
734         -abs(ESMF_TimeIntervalNegAbsValue%basetime%Sn )
736       end function ESMF_TimeIntervalNegAbsValue
738 !------------------------------------------------------------------------------
740 ! This section includes overloaded operators defined only for TimeInterval
741 ! (not inherited from BaseTime)
742 ! Note:  these functions do not have a return code, since F90 forbids more
743 ! than 2 arguments for arithmetic overloaded operators
745 !------------------------------------------------------------------------------
747 !!!!!!!!!!!!!!!!!! added jm 20051012
748 ! new WRF-specific function, Divide two time intervals and return the whole integer, without remainder
749       function ESMF_TimeIntervalDIVQuot(timeinterval1, timeinterval2)
751 ! !RETURN VALUE:
752       INTEGER :: ESMF_TimeIntervalDIVQuot 
754 ! !ARGUMENTS:
755       type(ESMF_TimeInterval), intent(in) :: timeinterval1
756       type(ESMF_TimeInterval), intent(in) :: timeinterval2
758 ! !LOCAL
759       INTEGER :: retval, isgn, rc
760       type(ESMF_TimeInterval) :: zero, i1,i2
762 ! !DESCRIPTION:
763 !     Returns timeinterval1 divided by timeinterval2 as a fraction quotient.
765 !     The arguments are:
766 !     \begin{description}
767 !     \item[timeinterval1]
768 !          The dividend
769 !     \item[timeinterval2]
770 !          The divisor
771 !     \end{description}
773 ! !REQUIREMENTS:
774 !     TMG1.5.5
775 !EOP
777       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalDIVQuot arg1' )
778       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalDIVQuot arg2' )
780       call ESMF_TimeIntervalSet( zero, rc=rc )
781       i1 = timeinterval1
782       i2 = timeinterval2
783       isgn = 1
784       if ( i1 .LT. zero ) then
785         i1 = ESMF_TimeIntervalProdI(i1, -1)
786         isgn = -isgn
787       endif
788       if ( i2 .LT. zero ) then
789         i2 = ESMF_TimeIntervalProdI(i2, -1)
790         isgn = -isgn
791       endif
792 ! repeated subtraction
793       retval = 0
794       DO WHILE (  i1 .GE. i2 )
795         i1 = i1 - i2
796         retval = retval + 1
797       ENDDO
798       retval = retval * isgn
800       ESMF_TimeIntervalDIVQuot = retval
802       end function ESMF_TimeIntervalDIVQuot
803 !!!!!!!!!!!!!!!!!!
807 !------------------------------------------------------------------------------
808 !BOP
809 ! !IROUTINE:  ESMF_TimeIntervalQuotI - Divide time interval by an integer, return time interval result 
811 ! !INTERFACE:
812       function ESMF_TimeIntervalQuotI(timeinterval, divisor)
814 ! !RETURN VALUE:
815       type(ESMF_TimeInterval) :: ESMF_TimeIntervalQuotI
817 ! !ARGUMENTS:
818       type(ESMF_TimeInterval), intent(in) :: timeinterval
819       integer, intent(in) :: divisor
821 ! !DESCRIPTION:
822 !     Divides a {\tt ESMF\_TimeInterval} by an integer divisor, returns
823 !     quotient as a {\tt ESMF\_TimeInterval}
825 !     The arguments are:
826 !     \begin{description}
827 !     \item[timeinterval]
828 !          The dividend
829 !     \item[divisor]
830 !          Integer divisor
831 !     \end{description}
833 ! !REQUIREMENTS:
834 !     TMG1.5.6, TMG5.3, TMG7.2
835 !EOP
837 !PRINT *,'DEBUG ESMF_TimeIntervalQuotI() A:  S,Sn,Sd = ', &
838 !  timeinterval%basetime%S,timeinterval%basetime%Sn,timeinterval%basetime%Sd
839 !PRINT *,'DEBUG ESMF_TimeIntervalQuotI() A:  divisor = ', divisor
841       CALL timeintchecknormalized( timeinterval, 'ESMF_TimeIntervalQuotI arg1' )
843       IF ( divisor == 0 ) THEN
844         CALL wrf_error_fatal( 'ESMF_TimeIntervalQuotI:  divide by zero' )
845       ENDIF
846       ESMF_TimeIntervalQuotI = timeinterval
847 !PRINT *,'DEBUG ESMF_TimeIntervalQuotI() B:  S,Sn,Sd = ', &
848 !  ESMF_TimeIntervalQuotI%basetime%S,ESMF_TimeIntervalQuotI%basetime%Sn,ESMF_TimeIntervalQuotI%basetime%Sd
849       ESMF_TimeIntervalQuotI%basetime = &
850         timeinterval%basetime / divisor
851 !PRINT *,'DEBUG ESMF_TimeIntervalQuotI() C:  S,Sn,Sd = ', &
852 !  ESMF_TimeIntervalQuotI%basetime%S,ESMF_TimeIntervalQuotI%basetime%Sn,ESMF_TimeIntervalQuotI%basetime%Sd
854       CALL normalize_timeint( ESMF_TimeIntervalQuotI )
855 !PRINT *,'DEBUG ESMF_TimeIntervalQuotI() D:  S,Sn,Sd = ', &
856 !  ESMF_TimeIntervalQuotI%basetime%S,ESMF_TimeIntervalQuotI%basetime%Sn,ESMF_TimeIntervalQuotI%basetime%Sd
858       end function ESMF_TimeIntervalQuotI
860 !------------------------------------------------------------------------------
861 !BOP
862 ! !IROUTINE:   ESMF_TimeIntervalProdI - Multiply a time interval by an integer
864 ! !INTERFACE:
865       function ESMF_TimeIntervalProdI(timeinterval, multiplier)
867 ! !RETURN VALUE:
868       type(ESMF_TimeInterval) :: ESMF_TimeIntervalProdI
870 ! !ARGUMENTS:
871       type(ESMF_TimeInterval), intent(in) :: timeinterval
872       integer, intent(in) :: multiplier
873 ! !LOCAL:
874       integer    :: rc
876 ! !DESCRIPTION:
877 !     Multiply a {\tt ESMF\_TimeInterval} by an integer, return product as a
878 !     {\tt ESMF\_TimeInterval}
880 !     The arguments are:
881 !     \begin{description}
882 !     \item[timeinterval]
883 !          The multiplicand
884 !     \item[mutliplier]
885 !          Integer multiplier
886 !     \end{description}
888 ! !REQUIREMENTS:
889 !     TMG1.5.7, TMG7.2
890 !EOP
891       CALL timeintchecknormalized( timeinterval, 'ESMF_TimeIntervalProdI arg1' )
893       CALL ESMF_TimeIntervalSet( ESMF_TimeIntervalProdI, rc=rc )
894 !$$$move this into overloaded operator(*) in BaseTime
895       ESMF_TimeIntervalProdI%basetime%S  = &
896         timeinterval%basetime%S * INT( multiplier, ESMF_KIND_I8 )
897       ESMF_TimeIntervalProdI%basetime%Sn = &
898         timeinterval%basetime%Sn * INT( multiplier, ESMF_KIND_I8 )
899       ! Don't multiply Sd
900       ESMF_TimeIntervalProdI%basetime%Sd = timeinterval%basetime%Sd
901       CALL normalize_timeint( ESMF_TimeIntervalProdI )
903       end function ESMF_TimeIntervalProdI
905 !------------------------------------------------------------------------------
907 ! This section includes the inherited ESMF_BaseTime class overloaded operators
909 !------------------------------------------------------------------------------
910 !BOP
911 ! !IROUTINE:  ESMF_TimeIntervalSum - Add two time intervals together
913 ! !INTERFACE:
914       function ESMF_TimeIntervalSum(timeinterval1, timeinterval2)
916 ! !RETURN VALUE:
917       type(ESMF_TimeInterval) :: ESMF_TimeIntervalSum
919 ! !ARGUMENTS:
920       type(ESMF_TimeInterval), intent(in) :: timeinterval1
921       type(ESMF_TimeInterval), intent(in) :: timeinterval2
922 ! !LOCAL:
923       integer                             :: rc
924 ! !DESCRIPTION:
925 !     Add two {\tt ESMF\_TimeIntervals}, return sum as a
926 !     {\tt ESMF\_TimeInterval}.  Maps overloaded (+) operator interface
927 !     function to {\tt ESMF\_BaseTime} base class.
929 !     The arguments are:
930 !     \begin{description}
931 !     \item[timeinterval1]
932 !          The augend 
933 !     \item[timeinterval2]
934 !          The addend
935 !     \end{description}
937 ! !REQUIREMENTS:
938 !     TMG1.5.4, TMG2.4.4, TMG2.4.5, TMG2.4.6, TMG5.1, TMG5.2, 
939 !                 TMG7.2
940 !EOP
941       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalSum arg1' )
942       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalSum arg2' )
944       ESMF_TimeIntervalSum = timeinterval1
945       ESMF_TimeIntervalSum%basetime = ESMF_TimeIntervalSum%basetime + &
946                                       timeinterval2%basetime
948       CALL normalize_timeint( ESMF_TimeIntervalSum )
950       end function ESMF_TimeIntervalSum
952 !------------------------------------------------------------------------------
953 !BOP
954 ! !IROUTINE:  ESMF_TimeIntervalDiff - Subtract one time interval from another
955    
956 ! !INTERFACE:
957       function ESMF_TimeIntervalDiff(timeinterval1, timeinterval2)
959 ! !RETURN VALUE:
960       type(ESMF_TimeInterval) :: ESMF_TimeIntervalDiff
962 ! !ARGUMENTS: 
963       type(ESMF_TimeInterval), intent(in) :: timeinterval1
964       type(ESMF_TimeInterval), intent(in) :: timeinterval2
965 ! !LOCAL:
966       integer                             :: rc
967 ! !DESCRIPTION:
968 !     Subtract timeinterval2 from timeinterval1, return remainder as a 
969 !     {\tt ESMF\_TimeInterval}.
970 !     Map overloaded (-) operator interface function to {\tt ESMF\_BaseTime}
971 !     base class.
973 !     The arguments are:
974 !     \begin{description}
975 !     \item[timeinterval1]
976 !          The minuend 
977 !     \item[timeinterval2]
978 !          The subtrahend
979 !     \end{description}
981 ! !REQUIREMENTS:
982 !     TMG1.5.4, TMG2.4.4, TMG2.4.5, TMG2.4.6, TMG5.1, TMG5.2, TMG7.2
983 !EOP
984       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalDiff arg1' )
985       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalDiff arg2' )
987       ESMF_TimeIntervalDiff = timeinterval1
988       ESMF_TimeIntervalDiff%basetime = ESMF_TimeIntervalDiff%basetime - &
989                                        timeinterval2%basetime
990       CALL normalize_timeint( ESMF_TimeIntervalDiff )
992       end function ESMF_TimeIntervalDiff
994 !------------------------------------------------------------------------------
995 !BOP
996 ! !IROUTINE: ESMF_TimeIntervalEQ - Compare two time intervals for equality
998 ! !INTERFACE:
999       function ESMF_TimeIntervalEQ(timeinterval1, timeinterval2)
1001 ! !RETURN VALUE:
1002       logical :: ESMF_TimeIntervalEQ
1004 ! !ARGUMENTS:
1005       type(ESMF_TimeInterval), intent(in) :: timeinterval1
1006       type(ESMF_TimeInterval), intent(in) :: timeinterval2
1008 !DESCRIPTION:
1009 !     Return true if both given time intervals are equal, false otherwise.
1010 !     Maps overloaded (==) operator interface function to {\tt ESMF\_BaseTime}
1011 !     base class.
1013 !     The arguments are:
1014 !     \begin{description}
1015 !     \item[timeinterval1]
1016 !          First time interval to compare
1017 !     \item[timeinterval2]
1018 !          Second time interval to compare
1019 !     \end{description}
1021 ! !REQUIREMENTS:
1022 !     TMG1.5.3, TMG2.4.3, TMG7.2
1023 !EOP
1024       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalEQ arg1' )
1025       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalEQ arg2' )
1027 !$$$here...  move all this out of Meat.F90 ?  
1028       ! call ESMC_BaseTime base class function
1029       call c_ESMC_BaseTimeIntEQ(timeinterval1, timeinterval2, ESMF_TimeIntervalEQ)
1031       end function ESMF_TimeIntervalEQ
1033 !------------------------------------------------------------------------------
1034 !BOP
1035 ! !IROUTINE:  ESMF_TimeIntervalNE - Compare two time intervals for inequality
1037 ! !INTERFACE:
1038       function ESMF_TimeIntervalNE(timeinterval1, timeinterval2)
1040 ! !RETURN VALUE:
1041       logical :: ESMF_TimeIntervalNE
1043 ! !ARGUMENTS:
1044       type(ESMF_TimeInterval), intent(in) :: timeinterval1
1045       type(ESMF_TimeInterval), intent(in) :: timeinterval2
1047 ! !DESCRIPTION:
1048 !     Return true if both given time intervals are not equal, false otherwise.
1049 !     Maps overloaded (/=) operator interface function to {\tt ESMF\_BaseTime}
1050 !     base class.
1052 !     The arguments are:
1053 !     \begin{description}
1054 !     \item[timeinterval1]
1055 !          First time interval to compare
1056 !     \item[timeinterval2]
1057 !          Second time interval to compare
1058 !     \end{description}
1060 ! !REQUIREMENTS:
1061 !     TMG1.5.3, TMG2.4.3, TMG7.2
1062 !EOP
1063       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalNE arg1' )
1064       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalNE arg2' )
1066       ! call ESMC_BaseTime base class function
1067       call c_ESMC_BaseTimeIntNE(timeinterval1, timeinterval2, ESMF_TimeIntervalNE)
1069       end function ESMF_TimeIntervalNE
1071 !------------------------------------------------------------------------------
1072 !BOP
1073 ! !IROUTINE:  ESMF_TimeIntervalLT - Time interval 1 less than time interval 2 ?
1075 ! !INTERFACE:
1076       function ESMF_TimeIntervalLT(timeinterval1, timeinterval2)
1078 ! !RETURN VALUE:
1079       logical :: ESMF_TimeIntervalLT
1081 ! !ARGUMENTS:
1082       type(ESMF_TimeInterval), intent(in) :: timeinterval1
1083       type(ESMF_TimeInterval), intent(in) :: timeinterval2
1085 ! !DESCRIPTION:
1086 !     Return true if first time interval is less than second time interval,
1087 !     false otherwise. Maps overloaded (<) operator interface function to
1088 !     {\tt ESMF\_BaseTime} base class.
1090 !     The arguments are:
1091 !     \begin{description}
1092 !     \item[timeinterval1]
1093 !          First time interval to compare
1094 !     \item[timeinterval2]
1095 !          Second time interval to compare
1096 !     \end{description}
1098 ! !REQUIREMENTS:
1099 !     TMG1.5.3, TMG2.4.3, TMG7.2
1100 !EOP
1101       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalLT arg1' )
1102       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalLT arg2' )
1104       ! call ESMC_BaseTime base class function
1105       call c_ESMC_BaseTimeIntLT(timeinterval1, timeinterval2, ESMF_TimeIntervalLT)
1107       end function ESMF_TimeIntervalLT
1109 !------------------------------------------------------------------------------
1110 !BOP
1111 ! !IROUTINE:  ESMF_TimeIntervalGT - Time interval 1 greater than time interval 2?
1113 ! !INTERFACE:
1114       function ESMF_TimeIntervalGT(timeinterval1, timeinterval2)
1116 ! !RETURN VALUE:
1117       logical :: ESMF_TimeIntervalGT
1119 ! !ARGUMENTS:
1120       type(ESMF_TimeInterval), intent(in) :: timeinterval1
1121       type(ESMF_TimeInterval), intent(in) :: timeinterval2
1123 ! !DESCRIPTION:
1124 !     Return true if first time interval is greater than second time interval,
1125 !     false otherwise.  Maps overloaded (>) operator interface function to
1126 !     {\tt ESMF\_BaseTime} base class.
1128 !     The arguments are:
1129 !     \begin{description}
1130 !     \item[timeinterval1]
1131 !          First time interval to compare
1132 !     \item[timeinterval2]
1133 !          Second time interval to compare
1134 !     \end{description}
1136 ! !REQUIREMENTS:
1137 !     TMG1.5.3, TMG2.4.3, TMG7.2
1138 !EOP
1139       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalGT arg1' )
1140       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalGT arg2' )
1142       ! call ESMC_BaseTime base class function
1143       call c_ESMC_BaseTimeIntGT(timeinterval1, timeinterval2, ESMF_TimeIntervalGT)
1145       end function ESMF_TimeIntervalGT
1147 !------------------------------------------------------------------------------
1148 !BOP
1149 ! !IROUTINE:  ESMF_TimeIntervalLE - Time interval 1 less than or equal to time interval 2 ?
1151 ! !INTERFACE:
1152       function ESMF_TimeIntervalLE(timeinterval1, timeinterval2)
1154 ! !RETURN VALUE:
1155       logical :: ESMF_TimeIntervalLE
1157 ! !ARGUMENTS:
1158       type(ESMF_TimeInterval), intent(in) :: timeinterval1
1159       type(ESMF_TimeInterval), intent(in) :: timeinterval2
1161 ! !DESCRIPTION:
1162 !     Return true if first time interval is less than or equal to second time
1163 !     interval, false otherwise.
1164 !     Maps overloaded (<=) operator interface function to {\tt ESMF\_BaseTime}
1165 !     base class.
1167 !     The arguments are:
1168 !     \begin{description}
1169 !     \item[timeinterval1]
1170 !          First time interval to compare
1171 !     \item[timeinterval2]
1172 !          Second time interval to compare
1173 !     \end{description}
1175 ! !REQUIREMENTS:
1176 !     TMG1.5.3, TMG2.4.3, TMG7.2
1177 !EOP
1178       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalLE arg1' )
1179       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalLE arg2' )
1181       ! call ESMC_BaseTime base class function
1182       call c_ESMC_BaseTimeIntLE(timeinterval1, timeinterval2, ESMF_TimeIntervalLE)
1184       end function ESMF_TimeIntervalLE
1186 !------------------------------------------------------------------------------
1187 !BOP
1188 ! !IROUTINE:  ESMF_TimeIntervalGE - Time interval 1 greater than or equal to time interval 2 ?
1190 ! !INTERFACE:
1191       function ESMF_TimeIntervalGE(timeinterval1, timeinterval2)
1193 ! !RETURN VALUE:
1194       logical :: ESMF_TimeIntervalGE
1196 ! !ARGUMENTS:
1197       type(ESMF_TimeInterval), intent(in) :: timeinterval1
1198       type(ESMF_TimeInterval), intent(in) :: timeinterval2
1200 ! !DESCRIPTION:
1201 !     Return true if first time interval is greater than or equal to second
1202 !     time interval, false otherwise. Maps overloaded (>=) operator interface
1203 !     function to {\tt ESMF\_BaseTime} base class.
1205 !     The arguments are:
1206 !     \begin{description}
1207 !     \item[timeinterval1]
1208 !          First time interval to compare
1209 !     \item[timeinterval2]
1210 !          Second time interval to compare
1211 !     \end{description}
1213 ! !REQUIREMENTS:
1214 !     TMG1.5.3, TMG2.4.3, TMG7.2
1215 !EOP
1216       CALL timeintchecknormalized( timeinterval1, 'ESMF_TimeIntervalGE arg1' )
1217       CALL timeintchecknormalized( timeinterval2, 'ESMF_TimeIntervalGE arg2' )
1219       ! call ESMC_BaseTime base class function
1220       call c_ESMC_BaseTimeIntGE(timeinterval1, timeinterval2, ESMF_TimeIntervalGE)
1222       end function ESMF_TimeIntervalGE
1225 !------------------------------------------------------------------------------
1226 !BOP
1227 ! !IROUTINE:  ESMF_TimeIntervalIsPositive - Time interval greater than zero?
1229 ! !INTERFACE:
1230       function ESMF_TimeIntervalIsPositive(timeinterval)
1232 ! !RETURN VALUE:
1233       logical :: ESMF_TimeIntervalIsPositive
1235 ! !ARGUMENTS:
1236       type(ESMF_TimeInterval), intent(in) :: timeinterval
1238 ! !LOCALS:
1239       type(ESMF_TimeInterval) :: zerotimeint
1240       integer :: rcint
1242 ! !DESCRIPTION:
1243 !     Return true if time interval is greater than zero,  
1244 !     false otherwise. 
1246 !     The arguments are:
1247 !     \begin{description}
1248 !     \item[timeinterval]
1249 !          Time interval to compare
1250 !     \end{description}
1251 !EOP
1252       CALL timeintchecknormalized( timeinterval, &
1253                                    'ESMF_TimeIntervalIsPositive arg' )
1255       CALL ESMF_TimeIntervalSet ( zerotimeint, rc=rcint )
1256       IF ( rcint /= ESMF_SUCCESS ) THEN
1257         CALL wrf_error_fatal( &
1258           'ESMF_TimeIntervalIsPositive:  ESMF_TimeIntervalSet failed' )
1259       ENDIF
1260 ! hack for bug in PGI 5.1-x
1261 !      ESMF_TimeIntervalIsPositive = timeinterval > zerotimeint
1262       ESMF_TimeIntervalIsPositive = ESMF_TimeIntervalGT( timeinterval, &
1263                                                          zerotimeint )
1264       end function ESMF_TimeIntervalIsPositive
1266       end module ESMF_TimeIntervalMod