updated top-level README and version_decl for V4.4.2 (#1795)
[WRF.git] / external / esmf_time_f90 / ESMF_Time.F90
blob809331a1817d01684f90f9149c556d3202491897
2 !==============================================================================
4 !     ESMF Time Module
5       module WRF_ESMF_TimeMod
7 !==============================================================================
9 ! This file contains the Time class definition and all Time class methods.
11 !------------------------------------------------------------------------------
12 ! INCLUDES
13 #include <ESMF_TimeMgr.inc>
15 !==============================================================================
16 !BOPI
17 ! !MODULE: WRF_ESMF_TimeMod
19 ! !DESCRIPTION:
20 ! Part of Time Manager F90 API wrapper of C++ implemenation
22 ! Defines F90 wrapper entry points for corresponding
23 ! C++ class {\tt ESMC\_Time} implementation
25 ! See {\tt ../include/ESMC\_Time.h} for complete description
27 !------------------------------------------------------------------------------
28 ! !USES:
29       ! inherit from ESMF base class
30       use WRF_ESMF_BaseMod
32       ! inherit from base time class
33       use WRF_ESMF_BaseTimeMod
35       ! associated derived types
36       use WRF_ESMF_TimeIntervalMod
37       use WRF_ESMF_CalendarMod
38       use WRF_ESMF_Stubs
40       implicit none
42 !------------------------------------------------------------------------------
43 ! !PRIVATE TYPES:
44       private
45 !------------------------------------------------------------------------------
46 !     ! ESMF_Time
48 !     ! F90 class type to match C++ Time class in size only;
49 !     !  all dereferencing within class is performed by C++ implementation
51      type ESMF_Time
52        type(ESMF_BaseTime) :: basetime           ! inherit base class
53        ! time instant is expressed as year + basetime
54        integer :: YR
55        type(ESMF_Calendar), pointer :: calendar  ! associated calendar
56      end type
58 !------------------------------------------------------------------------------
59 ! !PUBLIC TYPES:
60       public ESMF_Time
61 !------------------------------------------------------------------------------
63 ! !PUBLIC MEMBER FUNCTIONS:
64       public ESMF_TimeGet
65       public ESMF_TimeSet
67 ! Required inherited and overridden ESMF_Base class methods
69       public ESMF_TimeCopy
71 ! !PRIVATE MEMBER FUNCTIONS:
73       private ESMF_TimeGetDayOfYear
74       private ESMF_TimeGetDayOfYearInteger
76 ! Inherited and overloaded from ESMF_BaseTime
78       ! NOTE:  ESMF_TimeInc, ESMF_TimeDec, ESMF_TimeDiff, ESMF_TimeEQ, 
79       !        ESMF_TimeNE, ESMF_TimeLT, ESMF_TimeGT, ESMF_TimeLE, and 
80       !        ESMF_TimeGE are PUBLIC only to work around bugs in the 
81       !        PGI 5.1-x compilers.  They should all be PRIVATE.  
83       public operator(+)
84       public ESMF_TimeInc
86       public operator(-)
87       public ESMF_TimeDec
88       public ESMF_TimeDec2
89       public ESMF_TimeDiff
91       public operator(.EQ.)
92       public ESMF_TimeEQ
94       public operator(.NE.)
95       public ESMF_TimeNE
97       public operator(.LT.)
98       public ESMF_TimeLT
100       public operator(.GT.)
101       public ESMF_TimeGT
103       public operator(.LE.)
104       public ESMF_TimeLE
106       public operator(.GE.)
107       public ESMF_TimeGE
109 !EOPI
111 !==============================================================================
113 ! INTERFACE BLOCKS
115 !==============================================================================
116 !BOP
117 ! !INTERFACE:
118       interface ESMF_TimeGetDayOfYear
120 ! !PRIVATE MEMBER FUNCTIONS:
121       module procedure ESMF_TimeGetDayOfYearInteger
123 ! !DESCRIPTION:
124 !     This interface overloads the {\tt ESMF\_GetDayOfYear} method
125 !     for the {\tt ESMF\_Time} class
127 !EOP
128       end interface
130 !------------------------------------------------------------------------------
131 !BOP
132 ! !INTERFACE:
133       interface operator(+)
135 ! !PRIVATE MEMBER FUNCTIONS:
136       module procedure ESMF_TimeInc, ESMF_TimeInc2
138 ! !DESCRIPTION:
139 !     This interface overloads the + operator for the {\tt ESMF\_Time} class
141 !EOP
142       end interface
144 !------------------------------------------------------------------------------
145 !BOP
146 ! !INTERFACE:
147       interface assignment (=)
149 ! !PRIVATE MEMBER FUNCTIONS:
150       module procedure ESMF_TimeCopy
152 ! !DESCRIPTION:
153 !     This interface overloads the = operator for the {\tt ESMF\_Time} class
155 !EOP
156       end interface
158 !------------------------------------------------------------------------------
159 !BOP
160 ! !INTERFACE:
161       interface operator(-)
163 ! !PRIVATE MEMBER FUNCTIONS:
164       module procedure ESMF_TimeDec, ESMF_TimeDec2
166 ! !DESCRIPTION:
167 !     This interface overloads the - operator for the {\tt ESMF\_Time} class
169 !EOP
170       end interface
172 !------------------------------------------------------------------------------
173 !BOP
174 ! !INTERFACE:
175       interface operator(-)
177 ! !PRIVATE MEMBER FUNCTIONS:
178       module procedure ESMF_TimeDiff
180 ! !DESCRIPTION:
181 !     This interface overloads the - operator for the {\tt ESMF\_Time} class
183 !EOP
184       end interface
186 !------------------------------------------------------------------------------
187 !BOP
188 ! !INTERFACE:
189       interface operator(.EQ.)
191 ! !PRIVATE MEMBER FUNCTIONS:
192       module procedure ESMF_TimeEQ
194 ! !DESCRIPTION:
195 !     This interface overloads the .EQ. operator for the {\tt ESMF\_Time} class
197 !EOP
198       end interface
200 !------------------------------------------------------------------------------
201 !BOP
202 ! !INTERFACE:
203       interface operator(.NE.)
205 ! !PRIVATE MEMBER FUNCTIONS:
206       module procedure ESMF_TimeNE
208 ! !DESCRIPTION:
209 !     This interface overloads the .NE. operator for the {\tt ESMF\_Time} class
211 !EOP
212       end interface
214 !------------------------------------------------------------------------------
215 !BOP
216 ! !INTERFACE:
217       interface operator(.LT.)
219 ! !PRIVATE MEMBER FUNCTIONS:
220       module procedure ESMF_TimeLT
222 ! !DESCRIPTION:
223 !     This interface overloads the .LT. operator for the {\tt ESMF\_Time} class
225 !EOP
226       end interface
228 !------------------------------------------------------------------------------
229 !BOP
230 ! !INTERFACE:
231       interface operator(.GT.)
233 ! !PRIVATE MEMBER FUNCTIONS:
234       module procedure ESMF_TimeGT
236 ! !DESCRIPTION:
237 !     This interface overloads the .GT. operator for the {\tt ESMF\_Time} class
239 !EOP
240       end interface
242 !------------------------------------------------------------------------------
243 !BOP
244 ! !INTERFACE:
245       interface operator(.LE.)
247 ! !PRIVATE MEMBER FUNCTIONS:
248       module procedure ESMF_TimeLE
250 ! !DESCRIPTION:
251 !     This interface overloads the .LE. operator for the {\tt ESMF\_Time} class
253 !EOP
254       end interface
256 !------------------------------------------------------------------------------
257 !BOP
258 ! !INTERFACE:
259       interface operator(.GE.)
261 ! !PRIVATE MEMBER FUNCTIONS:
262       module procedure ESMF_TimeGE
264 ! !DESCRIPTION:
265 !     This interface overloads the .GE. operator for the {\tt ESMF\_Time} class
267 !EOP
268       end interface
270 !------------------------------------------------------------------------------
272 !==============================================================================
274       contains
276 !==============================================================================
278 ! Generic Get/Set routines which use F90 optional arguments
280 !------------------------------------------------------------------------------
281 !BOP
282 ! !IROUTINE: ESMF_TimeGet - Get value in user-specified units
284 ! !INTERFACE:
285       subroutine ESMF_TimeGet(time, YY, YRl, MM, DD, D, Dl, H, M, S, Sl, MS, &
286                               US, NS, d_, h_, m_, s_, ms_, us_, ns_, Sn, Sd, &
287                               dayOfYear, dayOfYear_r8, dayOfYear_intvl,      &
288                               timeString, rc)
290 ! !ARGUMENTS:
291       type(ESMF_Time), intent(in) :: time
292       integer, intent(out), optional :: YY
293       integer(ESMF_KIND_I8), intent(out), optional :: YRl
294       integer, intent(out), optional :: MM
295       integer, intent(out), optional :: DD
296       integer, intent(out), optional :: D
297       integer(ESMF_KIND_I8), intent(out), optional :: Dl
298       integer, intent(out), optional :: H
299       integer, intent(out), optional :: M
300       integer, intent(out), optional :: S
301       integer(ESMF_KIND_I8), intent(out), optional :: Sl
302       integer, intent(out), optional :: MS
303       integer, intent(out), optional :: US
304       integer, intent(out), optional :: NS
305       double precision, intent(out), optional :: d_
306       double precision, intent(out), optional :: h_
307       double precision, intent(out), optional :: m_
308       double precision, intent(out), optional :: s_
309       double precision, intent(out), optional :: ms_
310       double precision, intent(out), optional :: us_
311       double precision, intent(out), optional :: ns_
312       integer, intent(out), optional :: Sn
313       integer, intent(out), optional :: Sd
314       integer, intent(out), optional :: dayOfYear
315       ! dayOfYear_r8 = 1.0 at 0Z on 1 January, 1.5 at 12Z on
316       ! 1 January, etc.
317       real(ESMF_KIND_R8), intent(out), optional :: dayOfYear_r8
318       character (len=*), intent(out), optional :: timeString
319       type(ESMF_TimeInterval), intent(out), optional :: dayOfYear_intvl
320       integer, intent(out), optional :: rc
322       type(ESMF_TimeInterval) :: day_step
323       integer :: ierr
325 ! !DESCRIPTION:
326 !     Get the value of the {\tt ESMF\_Time} in units specified by the user
327 !     via F90 optional arguments.
329 !     Time manager represents and manipulates time internally with integers
330 !     to maintain precision. Hence, user-specified floating point values are
331 !     converted internally from integers.
333 !     See {\tt ../include/ESMC\_BaseTime.h and ../include/ESMC\_Time.h} for
334 !     complete description.
335 !     
336 !     The arguments are:
337 !     \begin{description}
338 !     \item[time]
339 !          The object instance to query
340 !     \item[{[YY]}]
341 !          Integer year CCYR (>= 32-bit)
342 !     \item[{[YRl]}]
343 !          Integer year CCYR (large, >= 64-bit)
344 !     \item[{[MM]}]
345 !          Integer month 1-12
346 !     \item[{[DD]}]
347 !          Integer day of the month 1-31
348 !     \item[{[D]}]
349 !          Integer Julian days (>= 32-bit)
350 !     \item[{[Dl]}]
351 !          Integer Julian days (large, >= 64-bit)
352 !     \item[{[H]}]
353 !          Integer hours
354 !     \item[{[M]}]
355 !          Integer minutes
356 !     \item[{[S]}]
357 !          Integer seconds (>= 32-bit)
358 !     \item[{[Sl]}]
359 !          Integer seconds (large, >= 64-bit)
360 !     \item[{[MS]}]
361 !          Integer milliseconds
362 !     \item[{[US]}]
363 !          Integer microseconds
364 !     \item[{[NS]}]
365 !          Integer nanoseconds
366 !     \item[{[d\_]}]
367 !          Double precision days
368 !     \item[{[h\_]}]
369 !          Double precision hours
370 !     \item[{[m\_]}]
371 !          Double precision minutes
372 !     \item[{[s\_]}]
373 !          Double precision seconds
374 !     \item[{[ms\_]}]
375 !          Double precision milliseconds
376 !     \item[{[us\_]}]
377 !          Double precision microseconds
378 !     \item[{[ns\_]}]
379 !          Double precision nanoseconds
380 !     \item[{[Sn]}]
381 !          Integer fractional seconds - numerator
382 !     \item[{[Sd]}]
383 !          Integer fractional seconds - denominator
384 !     \item[{[rc]}]
385 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
386 !     \end{description}
388 ! !REQUIREMENTS:
389 !     TMG2.1, TMG2.5.1, TMG2.5.6
390 !EOP
391       TYPE(ESMF_Time) :: begofyear
392       INTEGER :: year, month, dayofmonth, hour, minute, second
393       REAL(ESMF_KIND_R8) :: rsec
395       ierr = ESMF_SUCCESS
397       IF ( PRESENT( YY ) ) THEN
398         YY = time%YR
399       ENDIF
400       IF ( PRESENT( MM ) ) THEN
401         CALL timegetmonth( time, MM )
402       ENDIF
403       IF ( PRESENT( DD ) ) THEN
404         CALL timegetdayofmonth( time, DD )
405       ENDIF
407 !$$$ Push HMS down into ESMF_BaseTime from EVERYWHERE
408 !$$$ and THEN add ESMF scaling behavior when other args are present...  
409       IF ( PRESENT( H ) ) THEN
410         H = mod( time%basetime%S, SECONDS_PER_DAY ) / SECONDS_PER_HOUR
411       ENDIF
412       IF ( PRESENT( M ) ) THEN
413         M = mod( time%basetime%S, SECONDS_PER_HOUR) / SECONDS_PER_MINUTE
414       ENDIF
415       IF ( PRESENT( S ) ) THEN
416         S = mod( time%basetime%S, SECONDS_PER_MINUTE )
417       ENDIF
418       ! TBH:  HACK to allow DD and S to behave as in ESMF 2.1.0+ when 
419       ! TBH:  both are present and H and M are not.  
420       IF ( PRESENT( S ) .AND. PRESENT( DD ) ) THEN
421         IF ( ( .NOT. PRESENT( H ) ) .AND. ( .NOT. PRESENT( M ) ) ) THEN
422           S = mod( time%basetime%S, SECONDS_PER_DAY )
423         ENDIF
424       ENDIF
425       IF ( PRESENT( MS ) ) THEN
426         IF ( time%basetime%Sd /= 0 ) THEN
427           MS = NINT( ( time%basetime%Sn*1.0D0 / time%basetime%Sd*1.0D0 ) * 1000.0D0 )
428         ELSE
429           MS = 0
430         ENDIF
431       ENDIF
432       IF ( PRESENT( Sd ) .AND. PRESENT( Sn ) ) THEN
433         Sd = time%basetime%Sd
434         Sn = time%basetime%Sn
435       ENDIF
436       IF ( PRESENT( dayOfYear ) ) THEN
437         CALL ESMF_TimeGetDayOfYear( time, dayOfYear, rc=ierr )
438       ENDIF
439       IF ( PRESENT( dayOfYear_r8 ) ) THEN
440         ! 64-bit IEEE 754 has 52-bit mantisssa -- only need 25 bits to hold 
441         ! number of seconds in a year...  
442         rsec = REAL( time%basetime%S, ESMF_KIND_R8 )
443         IF ( time%basetime%Sd /= 0 ) THEN
444           rsec = rsec + ( REAL( time%basetime%Sn, ESMF_KIND_R8 ) / &
445                           REAL( time%basetime%Sd, ESMF_KIND_R8 ) )
446         ENDIF
447         dayOfYear_r8 = rsec / REAL( SECONDS_PER_DAY, ESMF_KIND_R8 )
448         ! start at 1
449         dayOfYear_r8 = dayOfYear_r8 + 1.0_ESMF_KIND_R8
450       ENDIF
451       IF ( PRESENT( timeString ) ) THEN
452         ! This duplication for YMD is an optimization that avoids calling 
453         ! timegetmonth() and timegetdayofmonth() when it is not needed.  
454         year = time%YR
455         CALL timegetmonth( time, month )
456         CALL timegetdayofmonth( time, dayofmonth )
457 !$$$ push HMS down into ESMF_BaseTime
458         hour = mod( time%basetime%S, SECONDS_PER_DAY ) / SECONDS_PER_HOUR
459         minute = mod( time%basetime%S, SECONDS_PER_HOUR) / SECONDS_PER_MINUTE
460         second = mod( time%basetime%S, SECONDS_PER_MINUTE )
461         CALL ESMFold_TimeGetString( year, month, dayofmonth, &
462                                     hour, minute, second, timeString )
463       ENDIF
464       IF ( PRESENT( dayOfYear_intvl ) ) THEN
465         year = time%YR
466         CALL ESMF_TimeSet( begofyear, yy=year, mm=1, dd=1, s=0, &
467                            calendar=time%calendar, rc=ierr )
468         IF ( ierr == ESMF_FAILURE)THEN
469            rc = ierr
470            RETURN
471         END IF
472         CALL ESMF_TimeIntervalSet( day_step, d=1, s=0, rc=ierr )
473         dayOfYear_intvl = time - begofyear + day_step
474       ENDIF
476       IF ( PRESENT( rc ) ) THEN
477         rc = ierr
478       ENDIF
480       end subroutine ESMF_TimeGet
482 !------------------------------------------------------------------------------
483 !BOP
484 ! !IROUTINE: ESMF_TimeSet - Initialize via user-specified unit set
486 ! !INTERFACE:
487       subroutine ESMF_TimeSet(time, YY, YRl, MM, DD, D, Dl, H, M, S, Sl, &
488                               MS, US, NS, d_, h_, m_, s_, ms_, us_, ns_, &
489                               Sn, Sd, calendar, rc)
491 ! !ARGUMENTS:
492       type(ESMF_Time), intent(inout) :: time
493       integer, intent(in), optional :: YY
494       integer(ESMF_KIND_I8), intent(in), optional :: YRl
495       integer, intent(in), optional :: MM
496       integer, intent(in), optional :: DD
497       integer, intent(in), optional :: D
498       integer(ESMF_KIND_I8), intent(in), optional :: Dl
499       integer, intent(in), optional :: H
500       integer, intent(in), optional :: M
501       integer, intent(in), optional :: S
502       integer(ESMF_KIND_I8), intent(in), optional :: Sl
503       integer, intent(in), optional :: MS
504       integer, intent(in), optional :: US
505       integer, intent(in), optional :: NS
506       double precision, intent(in), optional :: d_
507       double precision, intent(in), optional :: h_
508       double precision, intent(in), optional :: m_
509       double precision, intent(in), optional :: s_
510       double precision, intent(in), optional :: ms_
511       double precision, intent(in), optional :: us_
512       double precision, intent(in), optional :: ns_
513       integer, intent(in), optional :: Sn
514       integer, intent(in), optional :: Sd
515       type(ESMF_Calendar), intent(in), target, optional :: calendar
516       integer, intent(out), optional :: rc
517       ! locals
518       INTEGER :: ierr
520 ! !DESCRIPTION:
521 !     Initializes a {\tt ESMF\_Time} with a set of user-specified units
522 !     via F90 optional arguments.
524 !     Time manager represents and manipulates time internally with integers
525 !     to maintain precision. Hence, user-specified floating point values are
526 !     converted internally to integers.
528 !     See {\tt ../include/ESMC\_BaseTime.h and ../include/ESMC\_Time.h} for
529 !     complete description.
531 !     The arguments are:
532 !     \begin{description}
533 !     \item[time]
534 !          The object instance to initialize
535 !     \item[{[YY]}]
536 !          Integer year CCYR (>= 32-bit)
537 !     \item[{[YRl]}]
538 !          Integer year CCYR (large, >= 64-bit)
539 !     \item[{[MM]}]
540 !          Integer month 1-12
541 !     \item[{[DD]}]
542 !          Integer day of the month 1-31
543 !     \item[{[D]}]
544 !          Integer Julian days (>= 32-bit)
545 !     \item[{[Dl]}]
546 !          Integer Julian days (large, >= 64-bit)
547 !     \item[{[H]}]
548 !          Integer hours
549 !     \item[{[M]}]
550 !          Integer minutes
551 !     \item[{[S]}]
552 !          Integer seconds (>= 32-bit)
553 !     \item[{[Sl]}]
554 !          Integer seconds (large, >= 64-bit)
555 !     \item[{[MS]}]
556 !          Integer milliseconds
557 !     \item[{[US]}]
558 !          Integer microseconds
559 !     \item[{[NS]}]
560 !          Integer nanoseconds
561 !     \item[{[d\_]}]
562 !          Double precision days
563 !     \item[{[h\_]}]
564 !          Double precision hours
565 !     \item[{[m\_]}]
566 !          Double precision minutes
567 !     \item[{[s\_]}]
568 !          Double precision seconds
569 !     \item[{[ms\_]}]
570 !          Double precision milliseconds
571 !     \item[{[us\_]}]
572 !          Double precision microseconds
573 !     \item[{[ns\_]}]
574 !          Double precision nanoseconds
575 !     \item[{[Sn]}]
576 !          Integer fractional seconds - numerator
577 !     \item[{[Sd]}]
578 !          Integer fractional seconds - denominator
579 !     \item[{[cal]}]
580 !          Associated {\tt Calendar}
581 !     \item[{[tz]}]
582 !          Associated timezone (hours offset from GMT, e.g. EST = -5)
583 !     \item[{[rc]}]
584 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
585 !     \end{description}
587 ! !REQUIREMENTS:
588 !     TMGn.n.n
589 !EOP
590 !  PRINT *,'DEBUG:  BEGIN ESMF_TimeSet()'
591 !$$$ push this down into ESMF_BaseTime constructor
592       time%basetime%S  = 0
593       time%basetime%Sn = 0
594       time%basetime%Sd = 0
596       IF ( PRESENT( rc ) ) rc = ESMF_FAILURE
597       time%YR = 0
598       IF ( PRESENT( YY ) ) THEN
599 !  PRINT *,'DEBUG:  ESMF_TimeSet():  YY = ',YY
600         time%YR = YY
601       ENDIF
602       IF ( PRESENT( MM ) ) THEN
603 !  PRINT *,'DEBUG:  ESMF_TimeSet():  MM = ',MM
604         CALL timeaddmonths( time, MM, ierr )
605         IF ( ierr == ESMF_FAILURE ) THEN
606           IF ( PRESENT( rc ) ) THEN
607             rc = ESMF_FAILURE
608             RETURN
609           ENDIF
610         ENDIF
611 !  PRINT *,'DEBUG:  ESMF_TimeSet():  back from timeaddmonths'
612       ENDIF
613       IF ( PRESENT( DD ) ) THEN
614 !$$$ no check for DD in range of days of month MM yet
615 !$$$ Must separate D and DD for correct interface!
616 !  PRINT *,'DEBUG:  ESMF_TimeSet():  DD = ',DD
617         time%basetime%S = time%basetime%S + &
618           ( SECONDS_PER_DAY * INT( (DD-1), ESMF_KIND_I8 ) )
619       ENDIF
620 !$$$ push H,M,S,Sn,Sd,MS down into ESMF_BaseTime constructor
621       IF ( PRESENT( H ) ) THEN
622 !  PRINT *,'DEBUG:  ESMF_TimeSet():  H = ',H
623         time%basetime%S = time%basetime%S + &
624           ( SECONDS_PER_HOUR * INT( H, ESMF_KIND_I8 ) )
625       ENDIF
626       IF ( PRESENT( M ) ) THEN
627 !  PRINT *,'DEBUG:  ESMF_TimeSet():  M = ',M
628         time%basetime%S = time%basetime%S + &
629           ( SECONDS_PER_MINUTE * INT( M, ESMF_KIND_I8 ) )
630       ENDIF
631       IF ( PRESENT( S ) ) THEN
632 !  PRINT *,'DEBUG:  ESMF_TimeSet():  S = ',S
633         time%basetime%S = time%basetime%S + &
634           INT( S, ESMF_KIND_I8 )
635       ENDIF
636       IF ( PRESENT( Sn ) .AND. ( .NOT. PRESENT( Sd ) ) ) THEN
637         CALL wrf_error_fatal( &
638           "ESMF_TimeSet:  Must specify Sd if Sn is specified")
639       ENDIF
640       IF ( PRESENT( Sd ) .AND. PRESENT( MS ) ) THEN
641         CALL wrf_error_fatal( &
642           "ESMF_TimeSet:  Must not specify both Sd and MS")
643       ENDIF
644       time%basetime%Sn = 0
645       time%basetime%Sd = 0
646       IF ( PRESENT( MS ) ) THEN
647 !  PRINT *,'DEBUG:  ESMF_TimeSet():  MS = ',MS
648         time%basetime%Sn = MS
649         time%basetime%Sd = 1000_ESMF_KIND_I8
650       ELSE IF ( PRESENT( Sd ) ) THEN
651 !  PRINT *,'DEBUG:  ESMF_TimeSet():  Sd = ',Sd
652         time%basetime%Sd = Sd
653         IF ( PRESENT( Sn ) ) THEN
654 !  PRINT *,'DEBUG:  ESMF_TimeSet():  Sn = ',Sn
655           time%basetime%Sn = Sn
656         ENDIF
657       ENDIF
658       IF ( PRESENT(calendar) )THEN
659 !  PRINT *,'DEBUG:  ESMF_TimeSet():  using passed-in calendar'
660 ! Note that the ugly hack of wrapping the call to ESMF_CalendarInitialized() 
661 ! inside this #ifdef is due to lack of support for compile-time initialization 
662 ! of components of Fortran derived types.  Some older compilers like PGI 5.1-x 
663 ! do not support this F95 feature.  In this case we only lose a safety check.  
664 #ifndef NO_DT_COMPONENT_INIT
665         IF ( .not. ESMF_CalendarInitialized( calendar ) )THEN
666            call wrf_error_fatal( "Error:: ESMF_CalendarCreate not "// &
667                                  "called on input Calendar")
668         END IF
669 #endif
670         time%Calendar => calendar
671       ELSE
672 !  PRINT *,'DEBUG:  ESMF_TimeSet():  using default calendar'
673         IF ( .not. ESMF_IsInitialized() )THEN
674            call wrf_error_fatal( "Error:: ESMF_Initialize not called")
675         END IF
676         time%Calendar => defaultCal
677       END IF
679 !  PRINT *,'DEBUG:  ESMF_TimeSet():  calling normalize_time()'
680 !$$$DEBUG
681 !IF ( time%basetime%Sd > 0 ) THEN
682 !  PRINT *,'DEBUG ESMF_TimeSet() before normalize:  S,Sn,Sd = ', &
683 !    time%basetime%S, time%basetime%Sn, time%basetime%Sd
684 !ENDIF
685 !$$$END DEBUG
686       CALL normalize_time( time )
687 !$$$DEBUG
688 !IF ( time%basetime%Sd > 0 ) THEN
689 !  PRINT *,'DEBUG ESMF_TimeSet() after normalize:  S,Sn,Sd = ', &
690 !    time%basetime%S, time%basetime%Sn, time%basetime%Sd
691 !ENDIF
692 !$$$END DEBUG
694 !  PRINT *,'DEBUG:  ESMF_TimeSet():  back from normalize_time()'
695       IF ( PRESENT( rc ) ) THEN
696         rc = ESMF_SUCCESS
697       ENDIF
699       end subroutine ESMF_TimeSet
701 !------------------------------------------------------------------------------
702 !BOP
703 ! !IROUTINE:  ESMFold_TimeGetString - Get time instant value in string format
705 ! !INTERFACE:
706       subroutine ESMFold_TimeGetString( year, month, dayofmonth, &
707                                         hour, minute, second, TimeString )
709 ! !ARGUMENTS:
710       integer, intent(in) :: year
711       integer, intent(in) :: month
712       integer, intent(in) :: dayofmonth
713       integer, intent(in) :: hour
714       integer, intent(in) :: minute
715       integer, intent(in) :: second
716       character*(*), intent(out) :: TimeString
717 ! !DESCRIPTION:
718 !     Convert {\tt ESMF\_Time}'s value into ISO 8601 format YYYY-MM-DDThh:mm:ss
720 !     The arguments are:
721 !     \begin{description}
722 !     \item[time]
723 !          The object instance to convert
724 !     \item[TimeString]
725 !          The string to return
726 !     \item[{[rc]}]
727 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
728 !     \end{description}
730 ! !REQUIREMENTS:
731 !     TMG2.4.7
732 !EOP
734 !PRINT *,'DEBUG:  ESMF_TimePrint():  YR,S,Sn,Sd = ',time%YR,time%basetime%S,time%basetime%Sn,time%basetime%Sd
735 !PRINT *,'DEBUG:  ESMF_TimePrint():  year = ',year
736 !PRINT *,'DEBUG:  ESMF_TimePrint():  month, dayofmonth = ',month,dayofmonth
737 !PRINT *,'DEBUG:  ESMF_TimePrint():  hour = ',hour
738 !PRINT *,'DEBUG:  ESMF_TimePrint():  minute = ',minute
739 !PRINT *,'DEBUG:  ESMF_TimePrint():  second = ',second
741 !$$$here...  add negative sign for YR<0
742 !$$$here...  add Sn, Sd ??
743 #ifdef PLANET
744       write(TimeString,FMT="(I4.4,'-',I5.5,'_',I2.2,':',I2.2,':',I2.2)") &
745              year,dayofmonth,hour,minute,second
746 #else
747       write(TimeString,FMT="(I4.4,'-',I2.2,'-',I2.2,'_',I2.2,':',I2.2,':',I2.2)") &
748              year,month,dayofmonth,hour,minute,second
749 #endif
751       end subroutine ESMFold_TimeGetString
753 !------------------------------------------------------------------------------
754 !BOP
755 ! !IROUTINE: ESMF_TimeGetDayOfYearInteger - Get time instant's day of the year as an integer value
757 ! !INTERFACE:
758       subroutine ESMF_TimeGetDayOfYearInteger(time, DayOfYear, rc)
760 ! !ARGUMENTS:
761       type(ESMF_Time), intent(in) :: time
762       integer, intent(out) :: DayOfYear
763       integer, intent(out), optional :: rc
765 ! !DESCRIPTION:
766 !     Get the day of the year the given {\tt ESMF\_Time} instant falls on
767 !     (1-365).  Returned as an integer value
769 !     The arguments are:
770 !     \begin{description}
771 !     \item[time]
772 !          The object instance to query
773 !     \item[DayOfYear]
774 !          The {\tt ESMF\_Time} instant's day of the year (1-365)
775 !     \item[{[rc]}]
776 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
777 !     \end{description}
779 ! !REQUIREMENTS:
780 !EOP
781       ! requires that time be normalized
782 !$$$ bug when Sn>0?  test
783 !$$$ add tests
784       DayOfYear = ( time%basetime%S / SECONDS_PER_DAY ) + 1
785       IF ( PRESENT( rc ) ) rc = ESMF_SUCCESS
786       end subroutine ESMF_TimeGetDayOfYearInteger
788 !------------------------------------------------------------------------------
789 !BOP
790 ! !IROUTINE: ESMF_TimeInc - Increment time instant with a time interval
792 ! !INTERFACE:
793       function ESMF_TimeInc(time, timeinterval)
795 ! !RETURN VALUE:
796       type(ESMF_Time) :: ESMF_TimeInc
798 ! !ARGUMENTS:
799       type(ESMF_Time), intent(in) :: time
800       type(ESMF_TimeInterval), intent(in) :: timeinterval
801 ! !LOCAL:
802       integer   :: rc
804 ! !DESCRIPTION:
805 !     Increment {\tt ESMF\_Time} instant with a {\tt ESMF\_TimeInterval},
806 !     return resulting {\tt ESMF\_Time} instant
808 !     Maps overloaded (+) operator interface function to
809 !     {\tt ESMF\_BaseTime} base class
811 !     The arguments are:
812 !     \begin{description}
813 !     \item[time]
814 !          The given {\tt ESMF\_Time} to increment
815 !     \item[timeinterval]
816 !          The {\tt ESMF\_TimeInterval} to add to the given {\tt ESMF\_Time}
817 !     \end{description}
819 ! !REQUIREMENTS:
820 !     TMG1.5.4, TMG2.4.4, TMG2.4.5, TMG2.4.6, TMG5.1, TMG5.2, TMG7.2
821 !EOP
823       ! copy ESMF_Time specific properties (e.g. calendar, timezone) 
824       ESMF_TimeInc = time
826       ! call ESMC_BaseTime base class function
827       call c_ESMC_BaseTimeSum(time, timeinterval, ESMF_TimeInc)
829       end function ESMF_TimeInc
831 ! this is added for certain compilers that don't deal with commutativity
833       function ESMF_TimeInc2(timeinterval, time)
834       type(ESMF_Time) :: ESMF_TimeInc2
835       type(ESMF_Time), intent(in) :: time
836       type(ESMF_TimeInterval), intent(in) :: timeinterval
837       ESMF_TimeInc2 = ESMF_TimeInc( time, timeinterval )
838       end function ESMF_TimeInc2
841 !------------------------------------------------------------------------------
842 !BOP
843 ! !IROUTINE: ESMF_TimeDec - Decrement time instant with a time interval
845 ! !INTERFACE:
846       function ESMF_TimeDec(time, timeinterval)
848 ! !RETURN VALUE:
849       type(ESMF_Time) :: ESMF_TimeDec
851 ! !ARGUMENTS:
852       type(ESMF_Time), intent(in) :: time
853       type(ESMF_TimeInterval), intent(in) :: timeinterval
854 ! !LOCAL:
855       integer   :: rc
857 ! !DESCRIPTION:
858 !     Decrement {\tt ESMF\_Time} instant with a {\tt ESMF\_TimeInterval},
859 !     return resulting {\tt ESMF\_Time} instant
861 !     Maps overloaded (-) operator interface function to
862 !     {\tt ESMF\_BaseTime} base class
864 !     The arguments are:
865 !     \begin{description}
866 !     \item[time]
867 !          The given {\tt ESMF\_Time} to decrement
868 !     \item[timeinterval]
869 !          The {\tt ESMF\_TimeInterval} to subtract from the given
870 !          {\tt ESMF\_Time}
871 !     \end{description}
872 !     
873 ! !REQUIREMENTS:
874 !     TMG1.5.4, TMG2.4.4, TMG2.4.5, TMG2.4.6, TMG5.1, TMG5.2, TMG7.2
875 !EOP
877       ! copy ESMF_Time specific properties (e.g. calendar, timezone) 
878       ESMF_TimeDec = time
880       ! call ESMC_BaseTime base class function
881        call c_ESMC_BaseTimeDec(time, timeinterval, ESMF_TimeDec)
883       end function ESMF_TimeDec
886 ! this is added for certain compilers that don't deal with commutativity
888       function ESMF_TimeDec2(timeinterval, time)
889       type(ESMF_Time) :: ESMF_TimeDec2
890       type(ESMF_Time), intent(in) :: time
891       type(ESMF_TimeInterval), intent(in) :: timeinterval
892       ESMF_TimeDec2 = ESMF_TimeDec( time, timeinterval )
893       end function ESMF_TimeDec2
895 !------------------------------------------------------------------------------
896 !BOP
897 ! !IROUTINE:  ESMF_TimeDiff - Return the difference between two time instants
899 ! !INTERFACE:
900       function ESMF_TimeDiff(time1, time2)
902 ! !RETURN VALUE:
903       type(ESMF_TimeInterval) :: ESMF_TimeDiff
905 ! !ARGUMENTS:
906       type(ESMF_Time), intent(in) :: time1
907       type(ESMF_Time), intent(in) :: time2
908 ! !LOCAL:
909       integer :: rc
911 ! !DESCRIPTION:
912 !     Return the {\tt ESMF\_TimeInterval} difference between two
913 !     {\tt ESMF\_Time} instants
915 !     Maps overloaded (-) operator interface function to
916 !     {\tt ESMF\_BaseTime} base class
918 !     The arguments are:
919 !     \begin{description}
920 !     \item[time1]
921 !          The first {\tt ESMF\_Time} instant
922 !     \item[time2]
923 !          The second {\tt ESMF\_Time} instant
924 !     \end{description}
926 ! !REQUIREMENTS:
927 !     TMG1.5.4, TMG2.4.4, TMG2.4.5, TMG2.4.6, TMG5.1, TMG5.2, TMG7.2
928 !EOP
930       ! call ESMC_BaseTime base class function
931       CALL ESMF_TimeIntervalSet( ESMF_TimeDiff, rc=rc )
932       call c_ESMC_BaseTimeDiff(time1, time2, ESMF_TimeDiff)
934       end function ESMF_TimeDiff
936 !------------------------------------------------------------------------------
937 !BOP
938 ! !IROUTINE: ESMF_TimeEQ - Compare two times for equality
940 ! !INTERFACE:
941       function ESMF_TimeEQ(time1, time2)
943 ! !RETURN VALUE:
944       logical :: ESMF_TimeEQ
946 ! !ARGUMENTS:
947       type(ESMF_Time), intent(in) :: time1
948       type(ESMF_Time), intent(in) :: time2
950 ! !DESCRIPTION:
951 !     Return true if both given {\tt ESMF\_Time} instants are equal, false
952 !     otherwise.  Maps overloaded (==) operator interface function to
953 !     {\tt ESMF\_BaseTime} base class.
955 !     The arguments are:
956 !     \begin{description}
957 !     \item[time1]
958 !          First time instant to compare
959 !     \item[time2]
960 !          Second time instant to compare
961 !     \end{description}
963 ! !REQUIREMENTS:
964 !     TMG1.5.3, TMG2.4.3, TMG7.2
965 !EOP
967       ! invoke C to C++ entry point for ESMF_BaseTime base class function
968       call c_ESMC_BaseTimeEQ(time1, time2, ESMF_TimeEQ)
970       end function ESMF_TimeEQ
972 !------------------------------------------------------------------------------
973 !BOP
974 ! !IROUTINE: ESMF_TimeNE - Compare two times for non-equality
976 ! !INTERFACE:
977       function ESMF_TimeNE(time1, time2)
979 ! !RETURN VALUE:
980       logical :: ESMF_TimeNE
982 ! !ARGUMENTS:
983       type(ESMF_Time), intent(in) :: time1
984       type(ESMF_Time), intent(in) :: time2
986 ! !DESCRIPTION:
987 !     Return true if both given {\tt ESMF\_Time} instants are not equal, false
988 !     otherwise.  Maps overloaded (/=) operator interface function to
989 !     {\tt ESMF\_BaseTime} base class.
991 !     The arguments are:
992 !     \begin{description}
993 !     \item[time1]
994 !          First time instant to compare
995 !     \item[time2]
996 !          Second time instant to compare
997 !     \end{description}
999 ! !REQUIREMENTS:
1000 !     TMG1.5.3, TMG2.4.3, TMG7.2
1001 !EOP
1003       ! call ESMC_BaseTime base class function
1004       call c_ESMC_BaseTimeNE(time1, time2, ESMF_TimeNE)
1006       end function ESMF_TimeNE
1008 !------------------------------------------------------------------------------
1009 !BOP
1010 ! !IROUTINE: ESMF_TimeLT - Time instant 1 less than time instant 2 ?
1012 ! !INTERFACE:
1013       function ESMF_TimeLT(time1, time2)
1015 ! !RETURN VALUE:
1016       logical :: ESMF_TimeLT
1018 ! !ARGUMENTS:
1019       type(ESMF_Time), intent(in) :: time1
1020       type(ESMF_Time), intent(in) :: time2
1022 ! !DESCRIPTION:
1023 !     Return true if first {\tt ESMF\_Time} instant is less than second
1024 !     {\tt ESMF\_Time} instant, false otherwise.  Maps overloaded (<)
1025 !     operator interface function to {\tt ESMF\_BaseTime} base class.
1027 !     The arguments are:
1028 !     \begin{description}
1029 !     \item[time1]
1030 !          First time instant to compare
1031 !     \item[time2]
1032 !          Second time instant to compare
1033 !     \end{description}
1035 ! !REQUIREMENTS:
1036 !     TMG1.5.3, TMG2.4.3, TMG7.2
1037 !EOP
1039       ! call ESMC_BaseTime base class function
1040       call c_ESMC_BaseTimeLT(time1, time2, ESMF_TimeLT)
1042       end function ESMF_TimeLT
1044 !------------------------------------------------------------------------------
1045 !BOP
1046 ! !IROUTINE: ESMF_TimeGT - Time instant 1 greater than time instant 2 ?
1048 ! !INTERFACE:
1049       function ESMF_TimeGT(time1, time2)
1051 ! !RETURN VALUE:
1052       logical :: ESMF_TimeGT
1054 ! !ARGUMENTS:
1055       type(ESMF_Time), intent(in) :: time1
1056       type(ESMF_Time), intent(in) :: time2
1058 ! !DESCRIPTION:
1059 !     Return true if first {\tt ESMF\_Time} instant is greater than second
1060 !     {\tt ESMF\_Time} instant, false otherwise.  Maps overloaded (>) operator
1061 !     interface function to {\tt ESMF\_BaseTime} base class.
1063 !     The arguments are:
1064 !     \begin{description}
1065 !     \item[time1]
1066 !          First time instant to compare
1067 !     \item[time2]
1068 !          Second time instant to compare
1069 !     \end{description}
1071 ! !REQUIREMENTS:
1072 !     TMG1.5.3, TMG2.4.3, TMG7.2
1073 !EOP
1075       ! call ESMC_BaseTime base class function
1076       call c_ESMC_BaseTimeGT(time1, time2, ESMF_TimeGT)
1078       end function ESMF_TimeGT
1080 !------------------------------------------------------------------------------
1081 !BOP
1082 ! !IROUTINE: ESMF_TimeLE - Time instant 1 less than or equal to time instant 2 ?
1084 ! !INTERFACE:
1085       function ESMF_TimeLE(time1, time2)
1087 ! !RETURN VALUE:
1088       logical :: ESMF_TimeLE
1090 ! !ARGUMENTS:
1091       type(ESMF_Time), intent(in) :: time1
1092       type(ESMF_Time), intent(in) :: time2
1094 ! !DESCRIPTION:
1095 !     Return true if first {\tt ESMF\_Time} instant is less than or equal to
1096 !     second {\tt ESMF\_Time} instant, false otherwise.  Maps overloaded (<=)
1097 !     operator interface function to {\tt ESMF\_BaseTime} base class.
1099 !     The arguments are:
1100 !     \begin{description}
1101 !     \item[time1]
1102 !          First time instant to compare
1103 !     \item[time2]
1104 !          Second time instant to compare
1105 !     \end{description}
1107 ! !REQUIREMENTS:
1108 !     TMG1.5.3, TMG2.4.3, TMG7.2
1109 !EOP
1111       ! call ESMC_BaseTime base class function
1112       call c_ESMC_BaseTimeLE(time1, time2, ESMF_TimeLE)
1114       end function ESMF_TimeLE
1116 !------------------------------------------------------------------------------
1117 !BOP
1118 ! !IROUTINE: ESMF_TimeGE - Time instant 1 greater than or equal to time instant 2 ?
1120 ! !INTERFACE:
1121       function ESMF_TimeGE(time1, time2)
1123 ! !RETURN VALUE:
1124       logical :: ESMF_TimeGE
1126 ! !ARGUMENTS:
1127       type(ESMF_Time), intent(in) :: time1
1128       type(ESMF_Time), intent(in) :: time2
1130 ! !DESCRIPTION:
1131 !     Return true if first {\tt ESMF\_Time} instant is greater than or equal to
1132 !     second {\tt ESMF\_Time} instant, false otherwise.  Maps overloaded (>=)
1133 !     operator interface function to {\tt ESMF\_BaseTime} base class.
1135 !     The arguments are:
1136 !     \begin{description}
1137 !     \item[time1]
1138 !          First time instant to compare
1139 !     \item[time2]
1140 !          Second time instant to compare
1141 !     \end{description}
1143 ! !REQUIREMENTS:
1144 !     TMG1.5.3, TMG2.4.3, TMG7.2
1145 !EOP
1147       ! call ESMC_BaseTime base class function
1148       call c_ESMC_BaseTimeGE(time1, time2, ESMF_TimeGE)
1150       end function ESMF_TimeGE
1152 !------------------------------------------------------------------------------
1153 !BOP
1154 ! !IROUTINE:  ESMF_TimeCopy - Copy a time-instance
1156 ! !INTERFACE:
1157       subroutine ESMF_TimeCopy(timeout, timein)
1159 ! !ARGUMENTS:
1160       type(ESMF_Time), intent(out) :: timeout
1161       type(ESMF_Time), intent(in) :: timein
1163 ! !DESCRIPTION:
1164 !     Copy a time-instance to a new instance.
1166 !     \item[{[rc]}]
1167 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
1168 !     \end{description}
1170 ! !REQUIREMENTS:
1171 !     TMGn.n.n
1172 !EOP
1173    
1174       timeout%basetime = timein%basetime
1175       timeout%YR       = timein%YR
1176       timeout%Calendar => timein%Calendar
1178       end subroutine ESMF_TimeCopy
1180       end module WRF_ESMF_TimeMod