Merge remote-tracking branch 'origin/release-v4.6.1'
[WRF.git] / external / esmf_time_f90 / Test1.F90
blobae7d29fc99d29fdb1c56a5db90f1788ca75e5a14
2 ! Sub-system tests for esmf_time_f90
4 ! Someday, switch over to funit!  
7 MODULE my_tests
8   USE ESMF_Mod
9   IMPLICIT NONE
11   ! Set this to .TRUE. to make wrf_error_fatal3() print a message on failure 
12   ! instead of stopping the program.  Use for testing only (since we cannot 
13   ! catch exceptions in Fortran90!!)  
14   LOGICAL :: WRF_ERROR_FATAL_PRINT = .FALSE.
16 CONTAINS
18   ! Test printing of an ESMF_Time or ESMF_TimeInterval object.  
19   !
20   ! Correct results are also passed in through this interface and compared 
21   ! with computed results.  PASS/FAIL messages are printed.  
22   !
23   SUBROUTINE test_print(  t_yy,  t_mm,  t_dd,  t_h,  t_m,  t_s, t_sn, t_sd, &
24                          ti_yy, ti_mm, ti_dd, ti_h, ti_m, ti_s, ti_sn, ti_sd, &
25                          res_str, testname, expect_error )
26     INTEGER, INTENT(IN), OPTIONAL :: t_YY
27     INTEGER, INTENT(IN), OPTIONAL :: t_MM  ! month
28     INTEGER, INTENT(IN), OPTIONAL :: t_DD  ! day of month
29     INTEGER, INTENT(IN), OPTIONAL :: t_H
30     INTEGER, INTENT(IN), OPTIONAL :: t_M
31     INTEGER, INTENT(IN), OPTIONAL :: t_S
32     INTEGER, INTENT(IN), OPTIONAL :: t_Sn
33     INTEGER, INTENT(IN), OPTIONAL :: t_Sd
34     INTEGER, INTENT(IN), OPTIONAL :: ti_YY
35     INTEGER, INTENT(IN), OPTIONAL :: ti_MM  ! month
36     INTEGER, INTENT(IN), OPTIONAL :: ti_DD  ! day of month
37     INTEGER, INTENT(IN), OPTIONAL :: ti_H
38     INTEGER, INTENT(IN), OPTIONAL :: ti_M
39     INTEGER, INTENT(IN), OPTIONAL :: ti_S
40     INTEGER, INTENT(IN), OPTIONAL :: ti_Sn
41     INTEGER, INTENT(IN), OPTIONAL :: ti_Sd
42     CHARACTER (LEN=*), INTENT(IN) :: res_str
43     CHARACTER (LEN=*), INTENT(IN), OPTIONAL :: testname
44     LOGICAL, OPTIONAL, INTENT(IN) :: expect_error
45     ! locals
46     INTEGER :: it_YY
47     INTEGER :: it_MM  ! month
48     INTEGER :: it_DD  ! day of month
49     INTEGER :: it_H
50     INTEGER :: it_M
51     INTEGER :: it_S
52     INTEGER :: it_Sn
53     INTEGER :: it_Sd
54     INTEGER :: iti_YY
55     INTEGER :: iti_MM  ! month
56     INTEGER :: iti_DD  ! day of month
57     INTEGER :: iti_H
58     INTEGER :: iti_M
59     INTEGER :: iti_S
60     INTEGER :: iti_Sn
61     INTEGER :: iti_Sd
62     LOGICAL :: is_t 
63     LOGICAL :: is_ti
64     CHARACTER (LEN=512) :: itestname
65     LOGICAL :: iexpect_error
66     INTEGER rc
67     TYPE(ESMF_Time)           :: t
68     TYPE(ESMF_TimeInterval)   :: ti
69     CHARACTER(LEN=ESMF_MAXSTR) :: str, computed_str, frac_str
70     CHARACTER(LEN=17) :: type_str
71     INTEGER :: res_len, computed_len, Sn, Sd
72     LOGICAL :: test_passed
74 !  PRINT *,'DEBUG:  BEGIN test_print()'
75     it_YY = 0
76     it_MM = 1
77     it_DD = 1
78     it_H = 0
79     it_M = 0
80     it_S = 0
81     it_Sn = 0
82     it_Sd = 0
83     iti_YY = 0
84     iti_MM = 0
85     iti_DD = 0
86     iti_H = 0
87     iti_M = 0
88     iti_S = 0
89     iti_Sn = 0
90     iti_Sd = 0
91     itestname = ''
92     iexpect_error = .FALSE.
94     IF ( PRESENT( t_YY ) ) it_YY = t_YY
95     IF ( PRESENT( t_MM ) ) it_MM = t_MM
96     IF ( PRESENT( t_DD ) ) it_DD = t_DD
97     IF ( PRESENT( t_H ) ) it_H = t_H
98     IF ( PRESENT( t_M ) ) it_M = t_M
99     IF ( PRESENT( t_S ) ) it_S = t_S
100     IF ( PRESENT( t_Sn ) ) it_Sn = t_Sn
101     IF ( PRESENT( t_Sd ) ) it_Sd = t_Sd
102     IF ( PRESENT( ti_YY ) ) iti_YY = ti_YY
103     IF ( PRESENT( ti_MM ) ) iti_MM = ti_MM
104     IF ( PRESENT( ti_DD ) ) iti_DD = ti_DD
105     IF ( PRESENT( ti_H ) ) iti_H = ti_H
106     IF ( PRESENT( ti_M ) ) iti_M = ti_M
107     IF ( PRESENT( ti_S ) ) iti_S = ti_S
108     IF ( PRESENT( ti_Sn ) ) iti_Sn = ti_Sn
109     IF ( PRESENT( ti_Sd ) ) iti_Sd = ti_Sd
110     IF ( PRESENT( testname ) ) itestname = TRIM(testname)
111     IF ( PRESENT( expect_error ) ) iexpect_error = expect_error
113     ! Ensure that optional arguments are consistent...
114     is_t = ( PRESENT( t_YY ) .OR. PRESENT( t_MM ) .OR. &
115              PRESENT( t_DD ) .OR. PRESENT( t_H ) .OR.  &
116              PRESENT( t_M )  .OR. PRESENT( t_S ) .OR.  &
117              PRESENT( t_Sn )  .OR. PRESENT( t_Sd ) )
118     is_ti = ( PRESENT( ti_YY ) .OR. PRESENT( ti_MM ) .OR. &
119               PRESENT( ti_DD ) .OR. PRESENT( ti_H ) .OR.  &
120               PRESENT( ti_M )  .OR. PRESENT( ti_S ) .OR.  &
121               PRESENT( ti_Sn )  .OR. PRESENT( ti_Sd ) )
122     IF ( is_t .EQV. is_ti ) THEN
123       CALL wrf_error_fatal3( __FILE__ , __LINE__ , &
124         'ERROR test_print:  inconsistent args' )
125     ENDIF
127 !PRINT *,'DEBUG:  test_print():  init objects'
128     ! Initialize object to be tested
129     ! modify behavior of wrf_error_fatal3 for tests expected to fail
130     IF ( iexpect_error ) WRF_ERROR_FATAL_PRINT = .TRUE.
131     Sn = 0
132     Sd = 0
133     IF ( is_t ) THEN
134       type_str = 'ESMF_Time'
135 !PRINT *,'DEBUG:  test_print():  calling ESMF_TimeSet()'
136 !PRINT *,'DEBUG:  test_print():  YY,MM,DD,H,M,S,Sn,Sd = ', it_YY,it_MM,it_DD,it_H,it_M,it_S,it_Sn,it_Sd
137       CALL ESMF_TimeSet( t, YY=it_YY, MM=it_MM, DD=it_DD , &
138                              H=it_H, M=it_M, S=it_S, Sn=it_Sn, Sd=it_Sd, rc=rc )
139 !PRINT *,'DEBUG:  test_print():  back from ESMF_TimeSet()'
140       CALL test_check_error( ESMF_SUCCESS, rc, &
141                              TRIM(itestname)//'ESMF_TimeSet() ', &
142                              __FILE__ , &
143                              __LINE__  )
144 !PRINT *,'DEBUG:  test_print():  calling ESMF_TimeGet()'
145       CALL ESMF_TimeGet( t, timeString=computed_str, Sn=Sn, Sd=Sd, rc=rc )
146       CALL test_check_error( ESMF_SUCCESS, rc, &
147                             TRIM(itestname)//'ESMF_TimeGet() ', &
148                             __FILE__ , &
149                             __LINE__  )
150 !PRINT *,'DEBUG:  test_print():  back from ESMF_TimeGet(), computed_str = ',TRIM(computed_str)
151     ELSE
152       type_str = 'ESMF_TimeInterval'
153 !PRINT *,'DEBUG:  test_print():  calling ESMF_TimeIntervalSet()'
154       CALL ESMF_TimeIntervalSet( ti, YY=iti_YY, MM=iti_MM, &
155                                       D=iti_DD ,           &
156                                       H=iti_H, M=iti_M,    &
157                                       S=iti_S, Sn=iti_Sn, Sd=iti_Sd, rc=rc )
158       CALL test_check_error( ESMF_SUCCESS, rc, &
159                              TRIM(itestname)//'ESMF_TimeIntervalSet() ', &
160                              __FILE__ , &
161                              __LINE__  )
162 !PRINT *,'DEBUG:  test_print():  calling ESMF_TimeIntervalGet()'
163       CALL ESMF_TimeIntervalGet( ti, timeString=computed_str, Sn=Sn, Sd=Sd, rc=rc )
164       CALL test_check_error( ESMF_SUCCESS, rc, &
165                             TRIM(itestname)//'ESMF_TimeGet() ', &
166                             __FILE__ , &
167                             __LINE__  )
168     ENDIF
169     ! handle fractions
170     IF ( Sd > 0 ) THEN
171       IF ( Sn > 0 ) THEN
172         WRITE(frac_str,FMT="('+',I2.2,'/',I2.2)") abs(Sn), Sd
173       ELSE IF ( Sn < 0 ) THEN
174         WRITE(frac_str,FMT="('-',I2.2,'/',I2.2)") abs(Sn), Sd
175       ELSE
176         frac_str = ''
177       ENDIF
178       computed_str = TRIM(computed_str)//TRIM(frac_str)
179     ENDIF
180     ! restore default behavior of wrf_error_fatal3
181     IF ( iexpect_error ) WRF_ERROR_FATAL_PRINT = .FALSE.
182 !PRINT *,'DEBUG:  test_print():  done init objects'
184 !PRINT *,'DEBUG:  test_print():  check result'
185     ! check result
186     test_passed = .FALSE.
187     res_len = LEN_TRIM(res_str)
188     computed_len = LEN_TRIM(computed_str)
189     IF ( res_len == computed_len ) THEN
190       IF ( computed_str(1:computed_len) == res_str(1:res_len) ) THEN
191         test_passed = .TRUE.
192       ENDIF
193     ENDIF
194     IF ( test_passed ) THEN
195       WRITE(*,FMT='(A)') 'PASS:  '//TRIM(itestname)
196     ELSE
197       WRITE(*,'(9A)') 'FAIL:  ',TRIM(itestname),':  printing ',TRIM(type_str), &
198         '  expected <', TRIM(res_str),'>  but computed <',TRIM(computed_str),'>'
199     ENDIF
200 !PRINT *,'DEBUG:  END test_print()'
202   END SUBROUTINE test_print
206   ! Test the following arithmetic operations on ESMF_Time and 
207   ! ESMF_TimeInterval objects:
208   !  ESMF_Time         = ESMF_Time         + ESMF_TimeInterval
209   !  ESMF_Time         = ESMF_TimeInterval + ESMF_Time
210   !  ESMF_Time         = ESMF_Time         - ESMF_TimeInterval
211   !  ESMF_TimeInterval = ESMF_Time         - ESMF_Time        
212   !  ESMF_TimeInterval = ESMF_TimeInterval + ESMF_TimeInterval
213   !  ESMF_TimeInterval = ESMF_TimeInterval - ESMF_TimeInterval
214   !  ESMF_TimeInterval = ESMF_TimeInterval * INTEGER
215   !  ESMF_TimeInterval = ESMF_TimeInterval / INTEGER
216   !
217   ! Correct results are also passed in through this interface and compared 
218   ! with computed results.  PASS/FAIL messages are printed.  
219   !
220   ! Operations are expressed as res = op1 +|- op2
221   !
222   SUBROUTINE test_arithmetic( add_op, multiply_op,                                       &
223      op1_t_yy,  op1_t_mm,  op1_t_dd,  op1_t_h,  op1_t_m,  op1_t_s,  op1_t_sn,  op1_t_sd, &
224     op1_ti_yy, op1_ti_mm, op1_ti_dd, op1_ti_h, op1_ti_m, op1_ti_s, op1_ti_sn, op1_ti_sd, &
225      op2_t_yy,  op2_t_mm,  op2_t_dd,  op2_t_h,  op2_t_m,  op2_t_s,  op2_t_sn,  op2_t_sd, &
226     op2_ti_yy, op2_ti_mm, op2_ti_dd, op2_ti_h, op2_ti_m, op2_ti_s, op2_ti_sn, op2_ti_sd, &
227     op2_int,                                                                             &
228      res_t_yy,  res_t_mm,  res_t_dd,  res_t_h,  res_t_m,  res_t_s,  res_t_sn,  res_t_sd, &
229     res_ti_yy, res_ti_mm, res_ti_dd, res_ti_h, res_ti_m, res_ti_s, res_ti_sn, res_ti_sd, &
230     res_int, testname, expect_error )
231     LOGICAL, INTENT(IN), OPTIONAL :: add_op      ! .TRUE.=add, .FALSE.=subtract
232     LOGICAL, INTENT(IN), OPTIONAL :: multiply_op ! .TRUE.=multiply, .FALSE.=divide
233     INTEGER, INTENT(IN), OPTIONAL :: op1_t_YY
234     INTEGER, INTENT(IN), OPTIONAL :: op1_t_MM  ! month
235     INTEGER, INTENT(IN), OPTIONAL :: op1_t_DD  ! day of month
236     INTEGER, INTENT(IN), OPTIONAL :: op1_t_H
237     INTEGER, INTENT(IN), OPTIONAL :: op1_t_M
238     INTEGER, INTENT(IN), OPTIONAL :: op1_t_S
239     INTEGER, INTENT(IN), OPTIONAL :: op1_t_Sn
240     INTEGER, INTENT(IN), OPTIONAL :: op1_t_Sd
241     INTEGER, INTENT(IN), OPTIONAL :: op1_ti_YY
242     INTEGER, INTENT(IN), OPTIONAL :: op1_ti_MM  ! month
243     INTEGER, INTENT(IN), OPTIONAL :: op1_ti_DD  ! day of month
244     INTEGER, INTENT(IN), OPTIONAL :: op1_ti_H
245     INTEGER, INTENT(IN), OPTIONAL :: op1_ti_M
246     INTEGER, INTENT(IN), OPTIONAL :: op1_ti_S
247     INTEGER, INTENT(IN), OPTIONAL :: op1_ti_Sn
248     INTEGER, INTENT(IN), OPTIONAL :: op1_ti_Sd
249     INTEGER, INTENT(IN), OPTIONAL :: op2_t_YY
250     INTEGER, INTENT(IN), OPTIONAL :: op2_t_MM  ! month
251     INTEGER, INTENT(IN), OPTIONAL :: op2_t_DD  ! day of month
252     INTEGER, INTENT(IN), OPTIONAL :: op2_t_H
253     INTEGER, INTENT(IN), OPTIONAL :: op2_t_M
254     INTEGER, INTENT(IN), OPTIONAL :: op2_t_S
255     INTEGER, INTENT(IN), OPTIONAL :: op2_t_Sn
256     INTEGER, INTENT(IN), OPTIONAL :: op2_t_Sd
257     INTEGER, INTENT(IN), OPTIONAL :: op2_ti_YY
258     INTEGER, INTENT(IN), OPTIONAL :: op2_ti_MM  ! month
259     INTEGER, INTENT(IN), OPTIONAL :: op2_ti_DD  ! day of month
260     INTEGER, INTENT(IN), OPTIONAL :: op2_ti_H
261     INTEGER, INTENT(IN), OPTIONAL :: op2_ti_M
262     INTEGER, INTENT(IN), OPTIONAL :: op2_ti_S
263     INTEGER, INTENT(IN), OPTIONAL :: op2_ti_Sn
264     INTEGER, INTENT(IN), OPTIONAL :: op2_ti_Sd
265     INTEGER, INTENT(IN), OPTIONAL :: op2_int
266     INTEGER, INTENT(IN), OPTIONAL :: res_t_YY
267     INTEGER, INTENT(IN), OPTIONAL :: res_t_MM  ! month
268     INTEGER, INTENT(IN), OPTIONAL :: res_t_DD  ! day of month
269     INTEGER, INTENT(IN), OPTIONAL :: res_t_H
270     INTEGER, INTENT(IN), OPTIONAL :: res_t_M
271     INTEGER, INTENT(IN), OPTIONAL :: res_t_S
272     INTEGER, INTENT(IN), OPTIONAL :: res_t_Sn
273     INTEGER, INTENT(IN), OPTIONAL :: res_t_Sd
274     INTEGER, INTENT(IN), OPTIONAL :: res_ti_YY
275     INTEGER, INTENT(IN), OPTIONAL :: res_ti_MM  ! month
276     INTEGER, INTENT(IN), OPTIONAL :: res_ti_DD  ! day of month
277     INTEGER, INTENT(IN), OPTIONAL :: res_ti_H
278     INTEGER, INTENT(IN), OPTIONAL :: res_ti_M
279     INTEGER, INTENT(IN), OPTIONAL :: res_ti_S
280     INTEGER, INTENT(IN), OPTIONAL :: res_ti_Sn
281     INTEGER, INTENT(IN), OPTIONAL :: res_ti_Sd
282     INTEGER, INTENT(IN), OPTIONAL :: res_int
283     CHARACTER (LEN=*), OPTIONAL, INTENT(IN) :: testname
284     LOGICAL, OPTIONAL, INTENT(IN) :: expect_error
285     ! locals
286     LOGICAL :: iadd_op
287     LOGICAL :: isubtract_op
288     LOGICAL :: imultiply_op
289     LOGICAL :: idivide_op
290     INTEGER :: iop1_t_YY
291     INTEGER :: iop1_t_MM  ! month
292     INTEGER :: iop1_t_DD  ! day of month
293     INTEGER :: iop1_t_H
294     INTEGER :: iop1_t_M
295     INTEGER :: iop1_t_S
296     INTEGER :: iop1_t_Sn
297     INTEGER :: iop1_t_Sd
298     INTEGER :: iop1_ti_YY
299     INTEGER :: iop1_ti_MM  ! month
300     INTEGER :: iop1_ti_DD  ! day of month
301     INTEGER :: iop1_ti_H
302     INTEGER :: iop1_ti_M
303     INTEGER :: iop1_ti_S
304     INTEGER :: iop1_ti_Sn
305     INTEGER :: iop1_ti_Sd
306     INTEGER :: iop2_t_YY
307     INTEGER :: iop2_t_MM  ! month
308     INTEGER :: iop2_t_DD  ! day of month
309     INTEGER :: iop2_t_H
310     INTEGER :: iop2_t_M
311     INTEGER :: iop2_t_S
312     INTEGER :: iop2_t_Sn
313     INTEGER :: iop2_t_Sd
314     INTEGER :: iop2_ti_YY
315     INTEGER :: iop2_ti_MM  ! month
316     INTEGER :: iop2_ti_DD  ! day of month
317     INTEGER :: iop2_ti_H
318     INTEGER :: iop2_ti_M
319     INTEGER :: iop2_ti_S
320     INTEGER :: iop2_ti_Sn
321     INTEGER :: iop2_ti_Sd
322     INTEGER :: ires_t_YY
323     INTEGER :: ires_t_MM  ! month
324     INTEGER :: ires_t_DD  ! day of month
325     INTEGER :: ires_t_H
326     INTEGER :: ires_t_M
327     INTEGER :: ires_t_S
328     INTEGER :: ires_t_Sn
329     INTEGER :: ires_t_Sd
330     INTEGER :: ires_ti_YY
331     INTEGER :: ires_ti_MM  ! month
332     INTEGER :: ires_ti_DD  ! day of month
333     INTEGER :: ires_ti_H
334     INTEGER :: ires_ti_M
335     INTEGER :: ires_ti_S
336     INTEGER :: ires_ti_Sn
337     INTEGER :: ires_ti_Sd
338     LOGICAL :: op1_is_t , op2_is_t , res_is_t
339     LOGICAL :: op1_is_ti, op2_is_ti, res_is_ti, op2_is_int
340     LOGICAL :: res_is_int
341     INTEGER :: num_ops, num_op1, num_op2, num_res
342     LOGICAL :: unsupported_op, test_passed
343     CHARACTER (LEN=512) :: itestname
344     LOGICAL :: iexpect_error
345     INTEGER :: rc
346     INTEGER :: computed_int, Sn, Sd
347     TYPE(ESMF_Time)           :: op1_t , op2_t , res_t, computed_t
348     TYPE(ESMF_TimeInterval)   :: op1_ti, op2_ti, res_ti, computed_ti
349     CHARACTER(LEN=ESMF_MAXSTR) :: str, op1_str, op2_str, res_str, computed_str, frac_str
350     CHARACTER(LEN=1) :: op_str
351     CHARACTER(LEN=17) :: op1_type_str, op2_type_str, res_type_str
353     iadd_op = .FALSE.
354     isubtract_op = .FALSE.
355     imultiply_op = .FALSE.
356     idivide_op = .FALSE.
357     iop1_t_YY = 0
358     iop1_t_MM = 1
359     iop1_t_DD = 1
360     iop1_t_H = 0
361     iop1_t_M = 0
362     iop1_t_S = 0
363     iop1_t_Sn = 0
364     iop1_t_Sd = 0
365     iop1_ti_YY = 0
366     iop1_ti_MM = 0
367     iop1_ti_DD = 0
368     iop1_ti_H = 0
369     iop1_ti_M = 0
370     iop1_ti_S = 0
371     iop1_ti_Sn = 0
372     iop1_ti_Sd = 0
373     iop2_t_YY = 0
374     iop2_t_MM = 1
375     iop2_t_DD = 1
376     iop2_t_H = 0
377     iop2_t_M = 0
378     iop2_t_S = 0
379     iop2_t_Sn = 0
380     iop2_t_Sd = 0
381     iop2_ti_YY = 0
382     iop2_ti_MM = 0
383     iop2_ti_DD = 0
384     iop2_ti_H = 0
385     iop2_ti_M = 0
386     iop2_ti_S = 0
387     iop2_ti_Sn = 0
388     iop2_ti_Sd = 0
389     ires_t_YY = 0
390     ires_t_MM = 1
391     ires_t_DD = 1
392     ires_t_H = 0
393     ires_t_M = 0
394     ires_t_S = 0
395     ires_t_Sn = 0
396     ires_t_Sd = 0
397     ires_ti_YY = 0
398     ires_ti_MM = 0
399     ires_ti_DD = 0
400     ires_ti_H = 0
401     ires_ti_M = 0
402     ires_ti_S = 0
403     ires_ti_Sn = 0
404     ires_ti_Sd = 0
405     itestname = ''
406     iexpect_error = .FALSE.
408     IF ( PRESENT( add_op ) ) THEN
409       iadd_op = add_op
410       isubtract_op = ( .NOT. add_op )
411     ENDIF
412     IF ( PRESENT( multiply_op ) ) THEN
413       imultiply_op = multiply_op
414       idivide_op = ( .NOT. multiply_op )
415     ENDIF
416     num_ops = 0
417     IF ( iadd_op )      num_ops = num_ops + 1
418     IF ( isubtract_op ) num_ops = num_ops + 1
419     IF ( imultiply_op ) num_ops = num_ops + 1
420     IF ( idivide_op )   num_ops = num_ops + 1
421     IF ( num_ops /= 1 ) THEN
422       CALL wrf_error_fatal3( __FILE__ , __LINE__ , &
423         'ERROR test_arithmetic:  inconsistent operation' )
424     ENDIF
425     IF ( PRESENT( op1_t_YY ) ) iop1_t_YY = op1_t_YY
426     IF ( PRESENT( op1_t_MM ) ) iop1_t_MM = op1_t_MM
427     IF ( PRESENT( op1_t_DD ) ) iop1_t_DD = op1_t_DD
428     IF ( PRESENT( op1_t_H ) ) iop1_t_H = op1_t_H
429     IF ( PRESENT( op1_t_M ) ) iop1_t_M = op1_t_M
430     IF ( PRESENT( op1_t_S ) ) iop1_t_S = op1_t_S
431     IF ( PRESENT( op1_t_Sn ) ) iop1_t_Sn = op1_t_Sn
432     IF ( PRESENT( op1_t_Sd ) ) iop1_t_Sd = op1_t_Sd
433     IF ( PRESENT( op1_ti_YY ) ) iop1_ti_YY = op1_ti_YY
434     IF ( PRESENT( op1_ti_MM ) ) iop1_ti_MM = op1_ti_MM
435     IF ( PRESENT( op1_ti_DD ) ) iop1_ti_DD = op1_ti_DD
436     IF ( PRESENT( op1_ti_H ) ) iop1_ti_H = op1_ti_H
437     IF ( PRESENT( op1_ti_M ) ) iop1_ti_M = op1_ti_M
438     IF ( PRESENT( op1_ti_S ) ) iop1_ti_S = op1_ti_S
439     IF ( PRESENT( op1_ti_Sn ) ) iop1_ti_Sn = op1_ti_Sn
440     IF ( PRESENT( op1_ti_Sd ) ) iop1_ti_Sd = op1_ti_Sd
441     IF ( PRESENT( op2_t_YY ) ) iop2_t_YY = op2_t_YY
442     IF ( PRESENT( op2_t_MM ) ) iop2_t_MM = op2_t_MM
443     IF ( PRESENT( op2_t_DD ) ) iop2_t_DD = op2_t_DD
444     IF ( PRESENT( op2_t_H ) ) iop2_t_H = op2_t_H
445     IF ( PRESENT( op2_t_M ) ) iop2_t_M = op2_t_M
446     IF ( PRESENT( op2_t_S ) ) iop2_t_S = op2_t_S
447     IF ( PRESENT( op2_t_Sn ) ) iop2_t_Sn = op2_t_Sn
448     IF ( PRESENT( op2_t_Sd ) ) iop2_t_Sd = op2_t_Sd
449     IF ( PRESENT( op2_ti_YY ) ) iop2_ti_YY = op2_ti_YY
450     IF ( PRESENT( op2_ti_MM ) ) iop2_ti_MM = op2_ti_MM
451     IF ( PRESENT( op2_ti_DD ) ) iop2_ti_DD = op2_ti_DD
452     IF ( PRESENT( op2_ti_H ) ) iop2_ti_H = op2_ti_H
453     IF ( PRESENT( op2_ti_M ) ) iop2_ti_M = op2_ti_M
454     IF ( PRESENT( op2_ti_S ) ) iop2_ti_S = op2_ti_S
455     IF ( PRESENT( op2_ti_Sn ) ) iop2_ti_Sn = op2_ti_Sn
456     IF ( PRESENT( op2_ti_Sd ) ) iop2_ti_Sd = op2_ti_Sd
457     IF ( PRESENT( res_t_YY ) ) ires_t_YY = res_t_YY
458     IF ( PRESENT( res_t_MM ) ) ires_t_MM = res_t_MM
459     IF ( PRESENT( res_t_DD ) ) ires_t_DD = res_t_DD
460     IF ( PRESENT( res_t_H ) ) ires_t_H = res_t_H
461     IF ( PRESENT( res_t_M ) ) ires_t_M = res_t_M
462     IF ( PRESENT( res_t_S ) ) ires_t_S = res_t_S
463     IF ( PRESENT( res_t_Sn ) ) ires_t_Sn = res_t_Sn
464     IF ( PRESENT( res_t_Sd ) ) ires_t_Sd = res_t_Sd
465     IF ( PRESENT( res_ti_YY ) ) ires_ti_YY = res_ti_YY
466     IF ( PRESENT( res_ti_MM ) ) ires_ti_MM = res_ti_MM
467     IF ( PRESENT( res_ti_DD ) ) ires_ti_DD = res_ti_DD
468     IF ( PRESENT( res_ti_H ) ) ires_ti_H = res_ti_H
469     IF ( PRESENT( res_ti_M ) ) ires_ti_M = res_ti_M
470     IF ( PRESENT( res_ti_S ) ) ires_ti_S = res_ti_S
471     IF ( PRESENT( res_ti_Sn ) ) ires_ti_Sn = res_ti_Sn
472     IF ( PRESENT( res_ti_Sd ) ) ires_ti_Sd = res_ti_Sd
473     IF ( PRESENT( testname ) ) itestname = TRIM(testname)
474     IF ( PRESENT( expect_error ) ) iexpect_error = expect_error
476     ! Ensure that optional arguments are consistent...
477     op1_is_t = ( PRESENT( op1_t_YY ) .OR. PRESENT( op1_t_MM ) .OR. &
478                  PRESENT( op1_t_DD ) .OR. PRESENT( op1_t_H ) .OR.  &
479                  PRESENT( op1_t_M )  .OR. PRESENT( op1_t_S ) .OR.  &
480                  PRESENT( op1_t_Sn )  .OR. PRESENT( op1_t_Sd ) )
481     op1_is_ti = ( PRESENT( op1_ti_YY ) .OR. PRESENT( op1_ti_MM ) .OR. &
482                   PRESENT( op1_ti_DD ) .OR. PRESENT( op1_ti_H ) .OR.  &
483                   PRESENT( op1_ti_M )  .OR. PRESENT( op1_ti_S ) .OR.  &
484                   PRESENT( op1_ti_Sn )  .OR. PRESENT( op1_ti_Sd ) )
485     op2_is_t = ( PRESENT( op2_t_YY ) .OR. PRESENT( op2_t_MM ) .OR. &
486                  PRESENT( op2_t_DD ) .OR. PRESENT( op2_t_H ) .OR.  &
487                  PRESENT( op2_t_M )  .OR. PRESENT( op2_t_S ) .OR.  &
488                  PRESENT( op2_t_Sn )  .OR. PRESENT( op2_t_Sd ) )
489     op2_is_ti = ( PRESENT( op2_ti_YY ) .OR. PRESENT( op2_ti_MM ) .OR. &
490                   PRESENT( op2_ti_DD ) .OR. PRESENT( op2_ti_H ) .OR.  &
491                   PRESENT( op2_ti_M )  .OR. PRESENT( op2_ti_S ) .OR.  &
492                   PRESENT( op2_ti_Sn )  .OR. PRESENT( op2_ti_Sd ) )
493     op2_is_int = ( PRESENT( op2_int ) )
494     res_is_t = ( PRESENT( res_t_YY ) .OR. PRESENT( res_t_MM ) .OR. &
495                  PRESENT( res_t_DD ) .OR. PRESENT( res_t_H ) .OR.  &
496                  PRESENT( res_t_M )  .OR. PRESENT( res_t_S ) .OR.  &
497                  PRESENT( res_t_Sn )  .OR. PRESENT( res_t_Sd ) )
498     res_is_ti = ( PRESENT( res_ti_YY ) .OR. PRESENT( res_ti_MM ) .OR. &
499                   PRESENT( res_ti_DD ) .OR. PRESENT( res_ti_H ) .OR.  &
500                   PRESENT( res_ti_M )  .OR. PRESENT( res_ti_S ) .OR.  &
501                   PRESENT( res_ti_Sn )  .OR. PRESENT( res_ti_Sd ) )
502     res_is_int = ( PRESENT( res_int ) )
503     num_op1 = 0
504     IF ( op1_is_t   ) num_op1 = num_op1 + 1
505     IF ( op1_is_ti  ) num_op1 = num_op1 + 1
506     IF ( num_op1 /= 1 ) THEN
507       CALL wrf_error_fatal3( __FILE__ , __LINE__ , &
508         'ERROR test_arithmetic:  inconsistent args for op1' )
509     ENDIF
510     num_op2 = 0
511     IF ( op2_is_t   ) num_op2 = num_op2 + 1
512     IF ( op2_is_ti  ) num_op2 = num_op2 + 1
513     IF ( op2_is_int ) num_op2 = num_op2 + 1
514     IF ( num_op2 /= 1 ) THEN
515       CALL wrf_error_fatal3( __FILE__ , __LINE__ , &
516         'ERROR test_arithmetic:  inconsistent args for op2' )
517     ENDIF
518     num_res = 0
519     IF ( res_is_t   ) num_res = num_res + 1
520     IF ( res_is_ti  ) num_res = num_res + 1
521     IF ( res_is_int ) num_res = num_res + 1
522     IF ( num_res /= 1 ) THEN
523       CALL wrf_error_fatal3( __FILE__ , __LINE__ , &
524         'ERROR test_arithmetic:  inconsistent args for result' )
525     ENDIF
527     ! Initialize op1
528     IF ( op1_is_t ) THEN
529       op1_type_str = 'ESMF_Time'
530       CALL ESMF_TimeSet( op1_t, YY=iop1_t_YY, MM=iop1_t_MM, DD=iop1_t_DD , &
531                                  H=iop1_t_H, M=iop1_t_M, S=iop1_t_S, Sn=iop1_t_Sn, Sd=iop1_t_Sd, rc=rc )
532       CALL test_check_error( ESMF_SUCCESS, rc, &
533                              TRIM(itestname)//'ESMF_TimeSet() ', &
534                              __FILE__ , &
535                              __LINE__  )
536       CALL ESMF_TimeGet( op1_t, timeString=op1_str, Sn=Sn, Sd=Sd, rc=rc )
537       CALL test_check_error( ESMF_SUCCESS, rc, &
538                             TRIM(itestname)//'ESMF_TimeGet() ', &
539                             __FILE__ , &
540                             __LINE__  )
541       ! handle fractions
542       CALL fraction_to_string( Sn, Sd, frac_str )
543       op1_str = TRIM(op1_str)//TRIM(frac_str)
544     ELSE
545       op1_type_str = 'ESMF_TimeInterval'
546       CALL ESMF_TimeIntervalSet( op1_ti, YY=iop1_ti_YY, MM=iop1_ti_MM, &
547                                           D=iop1_ti_DD ,               &
548                                           H=iop1_ti_H, M=iop1_ti_M,    &
549                                           S=iop1_ti_S, Sn=iop1_ti_Sn, Sd=iop1_ti_Sd, rc=rc )
550       CALL test_check_error( ESMF_SUCCESS, rc, &
551                              TRIM(itestname)//'ESMF_TimeIntervalSet() ', &
552                              __FILE__ , &
553                              __LINE__  )
554       CALL ESMF_TimeIntervalGet( op1_ti, timeString=op1_str, Sn=Sn, Sd=Sd, rc=rc )
555       CALL test_check_error( ESMF_SUCCESS, rc, &
556                             TRIM(itestname)//'ESMF_TimeGet() ', &
557                             __FILE__ , &
558                             __LINE__  )
559       ! handle fractions
560       CALL fraction_to_string( Sn, Sd, frac_str )
561       op1_str = TRIM(op1_str)//TRIM(frac_str)
562     ENDIF
563     ! Initialize op2
564     IF ( op2_is_t ) THEN
565       op2_type_str = 'ESMF_Time'
566       CALL ESMF_TimeSet( op2_t, YY=iop2_t_YY, MM=iop2_t_MM, DD=iop2_t_DD , &
567                                  H=iop2_t_H, M=iop2_t_M, S=iop2_t_S, Sn=iop2_t_Sn, Sd=iop2_t_Sd, rc=rc )
568       CALL test_check_error( ESMF_SUCCESS, rc, &
569                              TRIM(itestname)//'ESMF_TimeSet() ', &
570                              __FILE__ , &
571                              __LINE__  )
572       CALL ESMF_TimeGet( op2_t, timeString=op2_str, Sn=Sn, Sd=Sd, rc=rc )
573       CALL test_check_error( ESMF_SUCCESS, rc, &
574                             TRIM(itestname)//'ESMF_TimeGet() ', &
575                             __FILE__ , &
576                             __LINE__  )
577       ! handle fractions
578       CALL fraction_to_string( Sn, Sd, frac_str )
579       op2_str = TRIM(op2_str)//TRIM(frac_str)
580     ELSE IF ( op2_is_ti ) THEN
581       op2_type_str = 'ESMF_TimeInterval'
582       CALL ESMF_TimeIntervalSet( op2_ti, YY=iop2_ti_YY, MM=iop2_ti_MM, &
583                                           D=iop2_ti_DD ,               &
584                                           H=iop2_ti_H, M=iop2_ti_M,    &
585                                           S=iop2_ti_S, Sn=iop2_ti_Sn, Sd=iop2_ti_Sd, rc=rc )
586       CALL test_check_error( ESMF_SUCCESS, rc, &
587                              TRIM(itestname)//'ESMF_TimeIntervalSet() ', &
588                              __FILE__ , &
589                              __LINE__  )
590       CALL ESMF_TimeIntervalGet( op2_ti, timeString=op2_str, Sn=Sn, Sd=Sd, rc=rc )
591       CALL test_check_error( ESMF_SUCCESS, rc, &
592                             TRIM(itestname)//'ESMF_TimeGet() ', &
593                             __FILE__ , &
594                             __LINE__  )
595       ! handle fractions
596       CALL fraction_to_string( Sn, Sd, frac_str )
597       op2_str = TRIM(op2_str)//TRIM(frac_str)
598     ELSE
599       op2_type_str = 'INTEGER'
600       IF ( op2_int > 0 ) THEN
601         WRITE(op2_str,FMT="('+',I8.8)") ABS(op2_int)
602       ELSE
603         WRITE(op2_str,FMT="('-',I8.8)") ABS(op2_int)
604       ENDIF
605     ENDIF
606     ! Initialize res
607     IF ( res_is_t ) THEN  ! result is ESMF_Time
608       res_type_str = 'ESMF_Time'
609       CALL ESMF_TimeSet( res_t, YY=ires_t_YY, MM=ires_t_MM, DD=ires_t_DD , &
610                                  H=ires_t_H, M=ires_t_M, S=ires_t_S, Sn=ires_t_Sn, Sd=ires_t_Sd, rc=rc )
611       CALL test_check_error( ESMF_SUCCESS, rc, &
612                              TRIM(itestname)//'ESMF_TimeSet() ', &
613                              __FILE__ , &
614                              __LINE__  )
615       CALL ESMF_TimeGet( res_t, timeString=res_str, Sn=Sn, Sd=Sd, rc=rc )
616       CALL test_check_error( ESMF_SUCCESS, rc, &
617                             TRIM(itestname)//'ESMF_TimeGet() ', &
618                             __FILE__ , &
619                             __LINE__  )
620       ! handle fractions
621       CALL fraction_to_string( Sn, Sd, frac_str )
622       res_str = TRIM(res_str)//TRIM(frac_str)
623     ELSE IF ( res_is_ti ) THEN  ! result is ESMF_TimeInterval
624       res_type_str = 'ESMF_TimeInterval'
625       CALL ESMF_TimeIntervalSet( res_ti, YY=ires_ti_YY, MM=ires_ti_MM, &
626                                           D=ires_ti_DD ,               &
627                                           H=ires_ti_H, M=ires_ti_M,    &
628                                           S=ires_ti_S, Sn=ires_ti_Sn, Sd=ires_ti_Sd, rc=rc )
629       CALL test_check_error( ESMF_SUCCESS, rc, &
630                              TRIM(itestname)//'ESMF_TimeIntervalSet() ', &
631                              __FILE__ , &
632                              __LINE__  )
633       CALL ESMF_TimeIntervalGet( res_ti, timeString=res_str, Sn=Sn, Sd=Sd, rc=rc )
634       CALL test_check_error( ESMF_SUCCESS, rc, &
635                             TRIM(itestname)//'ESMF_TimeGet() ', &
636                             __FILE__ , &
637                             __LINE__  )
638       ! handle fractions
639       CALL fraction_to_string( Sn, Sd, frac_str )
640       res_str = TRIM(res_str)//TRIM(frac_str)
641     ELSE  ! result is INTEGER
642       res_type_str = 'INTEGER'
643       IF ( res_int > 0 ) THEN
644         WRITE(res_str,FMT="('+',I8.8)") ABS(res_int)
645       ELSE
646         WRITE(res_str,FMT="('-',I8.8)") ABS(res_int)
647       ENDIF
648     ENDIF
650     ! perform requested operation
651     unsupported_op = .FALSE.
652     ! modify behavior of wrf_error_fatal3 for operator being tested
653     IF ( iexpect_error ) WRF_ERROR_FATAL_PRINT = .TRUE.
654     ! add
655     IF ( iadd_op ) THEN
656       op_str = '+'
657       IF ( res_is_t ) THEN  ! result is ESMF_Time
658         IF ( op1_is_t .AND. op2_is_ti ) THEN
659           !  ESMF_Time         = ESMF_Time         + ESMF_TimeInterval
660           computed_t = op1_t + op2_ti
661         ELSE IF ( op1_is_ti .AND. op2_is_t ) THEN
662           !  ESMF_Time         = ESMF_TimeInterval + ESMF_Time
663           computed_t = op1_ti + op2_t
664         ELSE
665           unsupported_op = .TRUE.
666         ENDIF
667       ELSE  ! result is ESMF_TimeInterval
668         IF ( op1_is_ti .AND. op2_is_ti ) THEN
669           !  ESMF_TimeInterval = ESMF_TimeInterval + ESMF_TimeInterval
670           computed_ti = op1_ti + op2_ti
671         ELSE
672           unsupported_op = .TRUE.
673         ENDIF
674       ENDIF
675     ! subtract
676     ELSE  IF ( isubtract_op ) THEN
677       op_str = '-'
678       IF ( res_is_t ) THEN  ! result is ESMF_Time
679         IF ( op1_is_t .AND. op2_is_ti ) THEN
680           !  ESMF_Time         = ESMF_Time         - ESMF_TimeInterval
681           computed_t = op1_t - op2_ti
682         ELSE
683           unsupported_op = .TRUE.
684         ENDIF
685       ELSE  ! result is ESMF_TimeInterval
686         IF ( op1_is_t .AND. op2_is_t ) THEN
687           !  ESMF_TimeInterval = ESMF_Time         - ESMF_Time        
688           computed_ti = op1_t - op2_t
689         ELSE IF ( op1_is_ti .AND. op2_is_ti ) THEN
690           !  ESMF_TimeInterval = ESMF_TimeInterval - ESMF_TimeInterval
691           computed_ti = op1_ti - op2_ti
692         ELSE
693           unsupported_op = .TRUE.
694         ENDIF
695       ENDIF
696     ELSE  IF ( imultiply_op ) THEN
697       op_str = '*'
698       IF ( res_is_ti ) THEN  ! result is ESMF_TimeInterval
699         IF ( op1_is_ti .AND. op2_is_int ) THEN
700           !  ESMF_TimeInterval = ESMF_TimeInterval * INTEGER
701           computed_ti = op1_ti * op2_int
702         ELSE
703           unsupported_op = .TRUE.
704         ENDIF
705       ENDIF
706     ELSE  IF ( idivide_op ) THEN
707       op_str = '/'
708       IF ( res_is_ti ) THEN  ! result is ESMF_TimeInterval
709         IF ( op1_is_ti .AND. op2_is_int ) THEN
710           !  ESMF_TimeInterval = ESMF_TimeInterval / INTEGER
711           computed_ti = op1_ti / op2_int
712         ELSE
713           unsupported_op = .TRUE.
714         ENDIF
715       ELSE IF ( res_is_int ) THEN  ! result is INTEGER
716         IF ( op1_is_ti .AND. op2_is_ti ) THEN
717           !  INTEGER = ESMF_TimeInterval / ESMF_TimeInterval
718           ! number of whole time intervals
719           computed_int = ESMF_TimeIntervalDIVQuot( op1_ti , op2_ti )
720         ELSE
721           unsupported_op = .TRUE.
722         ENDIF
723       ENDIF
724     ENDIF
725     ! restore default behavior of wrf_error_fatal3
726     IF ( iexpect_error ) WRF_ERROR_FATAL_PRINT = .FALSE.
727     IF ( unsupported_op ) THEN
728       WRITE(str,*) 'ERROR test_arithmetic ',TRIM(itestname), &
729         ':  unsupported operation (',                           &
730         TRIM(res_type_str),' = ',TRIM(op1_type_str),' ',TRIM(op_str),' ', &
731         TRIM(op2_type_str),')'
732       CALL wrf_error_fatal3( __FILE__ , __LINE__ , str )
733     ENDIF
735     ! check result
736     test_passed = .FALSE.
737     IF ( res_is_t ) THEN  ! result is ESMF_Time
738       IF ( computed_t == res_t ) THEN
739         test_passed = .TRUE.
740       ELSE
741         CALL ESMF_TimeGet( computed_t, timeString=computed_str, Sn=Sn, Sd=Sd, rc=rc )
742         CALL test_check_error( ESMF_SUCCESS, rc, &
743                               TRIM(itestname)//'ESMF_TimeGet() ', &
744                               __FILE__ , &
745                               __LINE__  )
746         ! handle fractions
747         CALL fraction_to_string( Sn, Sd, frac_str )
748         computed_str = TRIM(computed_str)//TRIM(frac_str)
749       ENDIF
750     ELSE IF ( res_is_ti ) THEN  ! result is ESMF_TimeInterval
751       IF ( computed_ti == res_ti ) THEN
752         test_passed = .TRUE.
753       ELSE
754         CALL ESMF_TimeIntervalGet( computed_ti, timeString=computed_str, Sn=Sn, Sd=Sd, rc=rc )
755         CALL test_check_error( ESMF_SUCCESS, rc, &
756                               TRIM(itestname)//'ESMF_TimeGet() ', &
757                               __FILE__ , &
758                               __LINE__  )
759         ! handle fractions
760         CALL fraction_to_string( Sn, Sd, frac_str )
761         computed_str = TRIM(computed_str)//TRIM(frac_str)
762       ENDIF
763     ELSE  ! result is INTEGER
764       IF ( computed_int == res_int ) THEN
765         test_passed = .TRUE.
766       ELSE
767         IF ( computed_int > 0 ) THEN
768           WRITE(computed_str,FMT="('+',I8.8)") ABS(computed_int)
769         ELSE
770           WRITE(computed_str,FMT="('-',I8.8)") ABS(computed_int)
771         ENDIF
772       ENDIF
773     ENDIF
774     IF ( test_passed ) THEN
775       WRITE(*,FMT='(A)') 'PASS:  '//TRIM(itestname)
776     ELSE
777       WRITE(*,*) 'FAIL:  ',TRIM(itestname),':  (',                        &
778         TRIM(res_type_str),' = ',TRIM(op1_type_str),' ',TRIM(op_str),' ', &
779         TRIM(op2_type_str),')  expected ',                                &
780         TRIM(res_str),' = ',TRIM(op1_str),' ',TRIM(op_str),' ',           &
781         TRIM(op2_str),'  but computed ',TRIM(computed_str)
782     ENDIF
784   END SUBROUTINE test_arithmetic
788   ! simple clock creation and advance with add-subtract tests thrown in
789   ! no self checks (yet)
790   SUBROUTINE test_clock_advance(                                              &
791     start_yy, start_mm, start_dd, start_h, start_m, start_s,                  &
792      stop_yy,  stop_mm,  stop_dd,  stop_h,  stop_m,  stop_s,                  &
793     timestep_d, timestep_h, timestep_m, timestep_s, timestep_sn, timestep_sd, &
794     testname, increment_S, increment_Sn, increment_Sd )
795     INTEGER, INTENT(IN), OPTIONAL :: start_YY
796     INTEGER, INTENT(IN), OPTIONAL :: start_MM  ! month
797     INTEGER, INTENT(IN), OPTIONAL :: start_DD  ! day of month
798     INTEGER, INTENT(IN), OPTIONAL :: start_H
799     INTEGER, INTENT(IN), OPTIONAL :: start_M
800     INTEGER, INTENT(IN), OPTIONAL :: start_S
801     INTEGER, INTENT(IN), OPTIONAL :: stop_YY
802     INTEGER, INTENT(IN), OPTIONAL :: stop_MM  ! month
803     INTEGER, INTENT(IN), OPTIONAL :: stop_DD  ! day of month
804     INTEGER, INTENT(IN), OPTIONAL :: stop_H
805     INTEGER, INTENT(IN), OPTIONAL :: stop_M
806     INTEGER, INTENT(IN), OPTIONAL :: stop_S
807     INTEGER, INTENT(IN), OPTIONAL :: timestep_D  ! day
808     INTEGER, INTENT(IN), OPTIONAL :: timestep_H
809     INTEGER, INTENT(IN), OPTIONAL :: timestep_M
810     INTEGER, INTENT(IN), OPTIONAL :: timestep_S
811     INTEGER, INTENT(IN), OPTIONAL :: timestep_Sn
812     INTEGER, INTENT(IN), OPTIONAL :: timestep_Sd
813     CHARACTER (LEN=*), OPTIONAL, INTENT(IN) :: testname
814     INTEGER, INTENT(IN), OPTIONAL :: increment_S  ! add and subtract this 
815     INTEGER, INTENT(IN), OPTIONAL :: increment_Sn ! value each time step
816     INTEGER, INTENT(IN), OPTIONAL :: increment_Sd
818     ! locals
819     INTEGER :: istart_YY
820     INTEGER :: istart_MM  ! month
821     INTEGER :: istart_DD  ! day of month
822     INTEGER :: istart_H
823     INTEGER :: istart_M
824     INTEGER :: istart_S
825     INTEGER :: istop_YY
826     INTEGER :: istop_MM  ! month
827     INTEGER :: istop_DD  ! day of month
828     INTEGER :: istop_H
829     INTEGER :: istop_M
830     INTEGER :: istop_S
831     INTEGER :: itimestep_D  ! day
832     INTEGER :: itimestep_H
833     INTEGER :: itimestep_M
834     INTEGER :: itimestep_S
835     INTEGER :: itimestep_Sn
836     INTEGER :: itimestep_Sd
837     CHARACTER (LEN=512) :: itestname, itestfullname
838     INTEGER :: iincrement_S
839     INTEGER :: iincrement_Sn
840     INTEGER :: iincrement_Sd
841     INTEGER :: Sn, Sd
842     INTEGER rc
843     TYPE(ESMF_Time)           :: start_time, stop_time, current_time
844     TYPE(ESMF_Clock), POINTER :: domain_clock
845     TYPE(ESMF_TimeInterval)   :: timestep, increment
846     TYPE(ESMF_Time)           :: add_time, subtract_time
847     INTEGER :: itimestep
848     REAL(ESMF_KIND_R8) :: dayr8
849     CHARACTER(LEN=ESMF_MAXSTR) :: str, frac_str
851     istart_YY = 0
852     istart_MM = 1
853     istart_DD = 1
854     istart_H = 0
855     istart_M = 0
856     istart_S = 0
857     istop_YY = 0
858     istop_MM = 1
859     istop_DD = 1
860     istop_H = 0
861     istop_M = 0
862     istop_S = 0
863     itimestep_D = 0
864     itimestep_H = 0
865     itimestep_M = 0
866     itimestep_S = 0
867     itimestep_Sn = 0
868     itimestep_Sd = 0
869     itestname = ''
870     iincrement_S = 0
871     iincrement_Sn = 0
872     iincrement_Sd = 0
874     IF ( PRESENT( start_YY ) ) istart_YY = start_YY
875     IF ( PRESENT( start_MM ) ) istart_MM = start_MM
876     IF ( PRESENT( start_DD ) ) istart_DD = start_DD
877     IF ( PRESENT( start_H ) ) istart_H = start_H
878     IF ( PRESENT( start_M ) ) istart_M = start_M
879     IF ( PRESENT( start_S ) ) istart_S = start_S
880     IF ( PRESENT( stop_YY ) ) istop_YY = stop_YY
881     IF ( PRESENT( stop_MM ) ) istop_MM = stop_MM
882     IF ( PRESENT( stop_DD ) ) istop_DD = stop_DD
883     IF ( PRESENT( stop_H ) ) istop_H = stop_H
884     IF ( PRESENT( stop_M ) ) istop_M = stop_M
885     IF ( PRESENT( stop_S ) ) istop_S = stop_S
886     IF ( PRESENT( timestep_D ) ) itimestep_D = timestep_D
887     IF ( PRESENT( timestep_H ) ) itimestep_H = timestep_H
888     IF ( PRESENT( timestep_M ) ) itimestep_M = timestep_M
889     IF ( PRESENT( timestep_S ) ) itimestep_S = timestep_S
890     IF ( PRESENT( timestep_Sn ) ) itimestep_Sn = timestep_Sn
891     IF ( PRESENT( timestep_Sd ) ) itimestep_Sd = timestep_Sd
892     IF ( PRESENT( testname ) ) itestname = TRIM(testname)//'_'
893     IF ( PRESENT( increment_S ) ) iincrement_S = increment_S
894     IF ( PRESENT( increment_Sn ) ) iincrement_Sn = increment_Sn
895     IF ( PRESENT( increment_Sd ) ) iincrement_Sd = increment_Sd
897     ! Initialize start time, stop time, time step, clock for simple case. 
898     itestfullname = TRIM(itestname)//'SETUP'
899     CALL ESMF_TimeSet( start_time, YY=istart_YY, MM=istart_MM, DD=istart_DD , &
900                                    H=istart_H, M=istart_M, S=istart_S, rc=rc )
901     CALL test_check_error( ESMF_SUCCESS, rc, &
902                           TRIM(itestfullname)//'ESMF_TimeSet() ', &
903                           __FILE__ , &
904                           __LINE__  )
906     CALL ESMF_TimeGet( start_time, timeString=str, rc=rc )
907     CALL test_check_error( ESMF_SUCCESS, rc, &
908                           TRIM(itestfullname)//'ESMF_TimeGet() ', &
909                           __FILE__ , &
910                           __LINE__  )
911     WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  start_time = <',TRIM(str),'>'
913     CALL ESMF_TimeSet( stop_time, YY=istop_YY, MM=istop_MM, DD=istop_DD , &
914                                    H=istop_H, M=istop_M, S=istop_S, rc=rc )
915     CALL test_check_error( ESMF_SUCCESS, rc, &
916                           TRIM(itestfullname)//'ESMF_TimeSet() ', &
917                           __FILE__ , &
918                           __LINE__  )
920     CALL ESMF_TimeGet( stop_time, timeString=str, rc=rc )
921     CALL test_check_error( ESMF_SUCCESS, rc, &
922                           TRIM(itestfullname)//'ESMF_TimeGet() ', &
923                           __FILE__ , &
924                           __LINE__  )
925     WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  stop_time = <',TRIM(str),'>'
927     CALL ESMF_TimeIntervalSet( timestep, D=itimestep_D, H=itimestep_H, &
928                                          M=itimestep_M, S=itimestep_S, &
929                                          Sn=itimestep_Sn, Sd=itimestep_Sd, rc=rc )
930     CALL test_check_error( ESMF_SUCCESS, rc, &
931                           TRIM(itestfullname)//'ESMF_TimeIntervalSet() ', &
932                           __FILE__ , &
933                           __LINE__  )
935     CALL ESMF_TimeIntervalGet( timestep, timeString=str, Sn=Sn, Sd=Sd, rc=rc )
936     CALL test_check_error( ESMF_SUCCESS, rc, &
937                           TRIM(itestfullname)//'ESMF_TimeIntervalGet() ', &
938                           __FILE__ , &
939                           __LINE__  )
940     ! handle fractions
941     CALL fraction_to_string( Sn, Sd, frac_str )
942     str = TRIM(str)//TRIM(frac_str)
943     WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  timestep = <',TRIM(str),'>'
945     CALL ESMF_TimeIntervalSet( increment, S=iincrement_S, &
946                                Sn=iincrement_Sn, Sd=iincrement_Sd, rc=rc )
947     CALL test_check_error( ESMF_SUCCESS, rc, &
948                           TRIM(itestfullname)//'ESMF_TimeIntervalSet() ', &
949                           __FILE__ , &
950                           __LINE__  )
952     CALL ESMF_TimeIntervalGet( increment, timeString=str, Sn=Sn, Sd=Sd, rc=rc )
953     CALL test_check_error( ESMF_SUCCESS, rc, &
954                           TRIM(itestfullname)//'ESMF_TimeIntervalGet() ', &
955                           __FILE__ , &
956                           __LINE__  )
957     ! handle fractions
958     CALL fraction_to_string( Sn, Sd, frac_str )
959     str = TRIM(str)//TRIM(frac_str)
960     WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  increment = <',TRIM(str),'>'
962     ALLOCATE( domain_clock )
963     domain_clock = ESMF_ClockCreate( TimeStep= timestep,  &
964                                      StartTime=start_time, &
965                                      StopTime= stop_time,  &
966                                      rc=rc )
967     CALL test_check_error( ESMF_SUCCESS, rc, &
968                           TRIM(itestfullname)//'ESMF_ClockCreate() ', &
969                           __FILE__ , &
970                           __LINE__  )
972     CALL ESMF_ClockGet( domain_clock, CurrTime=current_time, &
973                         rc=rc )
974     CALL test_check_error( ESMF_SUCCESS, rc, &
975                           TRIM(itestfullname)//'ESMF_ClockGet() ', &
976                           __FILE__ , &
977                           __LINE__  )
979     CALL ESMF_TimeGet( current_time, timeString=str, Sn=Sn, Sd=Sd, rc=rc )
980     CALL test_check_error( ESMF_SUCCESS, rc, &
981                           TRIM(itestfullname)//'ESMF_TimeGet() ', &
982                           __FILE__ , &
983                           __LINE__  )
984     CALL fraction_to_string( Sn, Sd, frac_str )
985     str = TRIM(str)//TRIM(frac_str)
986     WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  clock current_time = <',TRIM(str),'>'
988     CALL ESMF_TimeGet( current_time, dayOfYear_r8=dayr8, rc=rc )
989     CALL test_check_error( ESMF_SUCCESS, rc, &
990                           TRIM(itestfullname)//'ESMF_TimeGet() ', &
991                           __FILE__ , &
992                           __LINE__  )
993     WRITE(*,FMT='(A,A,F10.6,A)') TRIM(itestfullname),':  current_time dayOfYear_r8 = < ',dayr8,' >'
995     subtract_time = current_time - increment
996     CALL ESMF_TimeGet( subtract_time, timeString=str, Sn=Sn, Sd=Sd, rc=rc )
997     CALL test_check_error( ESMF_SUCCESS, rc, &
998                           TRIM(itestfullname)//'ESMF_TimeGet() ', &
999                           __FILE__ , &
1000                           __LINE__  )
1001     CALL fraction_to_string( Sn, Sd, frac_str )
1002     str = TRIM(str)//TRIM(frac_str)
1003     WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  current_time-increment = <',TRIM(str),'>'
1005     add_time = current_time + increment
1006     CALL ESMF_TimeGet( add_time, timeString=str, Sn=Sn, Sd=Sd, rc=rc )
1007     CALL test_check_error( ESMF_SUCCESS, rc, &
1008                           TRIM(itestfullname)//'ESMF_TimeGet() ', &
1009                           __FILE__ , &
1010                           __LINE__  )
1011     CALL fraction_to_string( Sn, Sd, frac_str )
1012     str = TRIM(str)//TRIM(frac_str)
1013     WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  current_time+increment = <',TRIM(str),'>'
1015     ! Advance clock.  
1016     itestfullname = TRIM(itestname)//'ADVANCE'
1017     itimestep = 0
1018     DO WHILE ( .NOT. ESMF_ClockIsStopTime(domain_clock ,rc=rc) )
1019       CALL test_check_error( ESMF_SUCCESS, rc, &
1020                             TRIM(itestfullname)//'ESMF_ClockIsStopTime() ', &
1021                             __FILE__ , &
1022                             __LINE__  )
1023       itimestep = itimestep + 1
1025       CALL ESMF_ClockAdvance( domain_clock, rc=rc )
1026       CALL test_check_error( ESMF_SUCCESS, rc, &
1027                             TRIM(itestfullname)//'ESMF_ClockAdvance() ', &
1028                             __FILE__ , &
1029                             __LINE__  )
1031       CALL ESMF_ClockGet( domain_clock, CurrTime=current_time, &
1032                           rc=rc )
1033       CALL test_check_error( ESMF_SUCCESS, rc, &
1034                             TRIM(itestfullname)//'ESMF_ClockGet() ', &
1035                             __FILE__ , &
1036                             __LINE__  )
1038       CALL ESMF_TimeGet( current_time, timeString=str, Sn=Sn, Sd=Sd, rc=rc )
1039       CALL test_check_error( ESMF_SUCCESS, rc, &
1040                             TRIM(itestfullname)//'ESMF_TimeGet() ', &
1041                             __FILE__ , &
1042                             __LINE__  )
1043       CALL fraction_to_string( Sn, Sd, frac_str )
1044       str = TRIM(str)//TRIM(frac_str)
1045       WRITE(*,FMT='(A,A,I6.6,A,A,A)') TRIM(itestfullname),':  count = ', &
1046         itimestep,'  current_time = <',TRIM(str),'>'
1048       subtract_time = current_time - increment
1049       CALL ESMF_TimeGet( subtract_time, timeString=str, Sn=Sn, Sd=Sd, rc=rc )
1050       CALL test_check_error( ESMF_SUCCESS, rc, &
1051                             TRIM(itestfullname)//'ESMF_TimeGet() ', &
1052                             __FILE__ , &
1053                             __LINE__  )
1054       CALL fraction_to_string( Sn, Sd, frac_str )
1055       str = TRIM(str)//TRIM(frac_str)
1056       WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  current_time-increment = <',TRIM(str),'>'
1058       add_time = current_time + increment
1059       CALL ESMF_TimeGet( add_time, timeString=str, Sn=Sn, Sd=Sd, rc=rc )
1060       CALL test_check_error( ESMF_SUCCESS, rc, &
1061                             TRIM(itestfullname)//'ESMF_TimeGet() ', &
1062                             __FILE__ , &
1063                             __LINE__  )
1064       CALL fraction_to_string( Sn, Sd, frac_str )
1065       str = TRIM(str)//TRIM(frac_str)
1066       WRITE(*,FMT='(A,A,A,A)') TRIM(itestfullname),':  current_time+increment = <',TRIM(str),'>'
1068     ENDDO
1070     DEALLOCATE( domain_clock )
1071   
1072   END SUBROUTINE test_clock_advance
1074 END MODULE my_tests
1077 #if defined( TIME_F90_ONLY ) 
1079 ! TBH:  Improve the build of Test1.exe to use WRF versions of these 
1080 ! TBH:  routines and remove these hacked-in duplicates!!  
1082 SUBROUTINE wrf_abort
1083   IMPLICIT NONE
1084 #if defined( DM_PARALLEL ) && ! defined( STUBMPI )
1085   INCLUDE 'mpif.h'
1086   INTEGER ierr
1087   CALL mpi_abort(MPI_COMM_WORLD,1,ierr)
1088 #else
1089   STOP
1090 #endif
1091 END SUBROUTINE wrf_abort
1093 SUBROUTINE wrf_message( str )
1094   IMPLICIT NONE
1095   CHARACTER*(*) str
1096 #if defined( DM_PARALLEL ) && ! defined( STUBMPI)
1097   write(0,*) str
1098 #endif
1099   print*, str
1100 END SUBROUTINE wrf_message
1102 ! intentionally write to stderr only
1103 SUBROUTINE wrf_message2( str )
1104   IMPLICIT NONE
1105   CHARACTER*(*) str
1106   write(0,*) str
1107 END SUBROUTINE wrf_message2
1109 SUBROUTINE wrf_error_fatal3( file_str, line, str )
1110   USE my_tests
1111   IMPLICIT NONE
1112   CHARACTER*(*) file_str
1113   INTEGER , INTENT (IN) :: line  ! only print file and line if line > 0
1114   CHARACTER*(*) str
1115   CHARACTER*256 :: line_str
1116   write(line_str,'(i6)') line
1117   ! special behavior for testing since Fortran cannot catch exceptions
1118  IF ( WRF_ERROR_FATAL_PRINT ) THEN
1119   ! just print message and continue
1120   CALL wrf_message( 'ERROR IN FILE:  '//TRIM(file_str)//'  LINE:  '//TRIM(line_str) )
1121  ELSE
1122   ! normal behavior
1123 #if defined( DM_PARALLEL ) && ! defined( STUBMPI )
1124   CALL wrf_message( '-------------- FATAL CALLED ---------------' )
1125   ! only print file and line if line is positive
1126   IF ( line > 0 ) THEN
1127     CALL wrf_message( 'FATAL CALLED FROM FILE:  '//file_str//'  LINE:  '//TRIM(line_str) )
1128   ENDIF
1129   CALL wrf_message( str )
1130   CALL wrf_message( '-------------------------------------------' )
1131 #else
1132   CALL wrf_message2( '-------------- FATAL CALLED ---------------' )
1133   ! only print file and line if line is positive
1134   IF ( line > 0 ) THEN
1135     CALL wrf_message( 'FATAL CALLED FROM FILE:  '//file_str//'  LINE:  '//TRIM(line_str) )
1136   ENDIF
1137   CALL wrf_message2( str )
1138   CALL wrf_message2( '-------------------------------------------' )
1139 #endif
1140   CALL wrf_abort
1141  ENDIF
1142 END SUBROUTINE wrf_error_fatal3
1144 SUBROUTINE wrf_error_fatal( str )
1145   IMPLICIT NONE
1146   CHARACTER*(*) str
1147   CALL wrf_error_fatal3 ( ' ', 0, str )
1148 END SUBROUTINE wrf_error_fatal
1150 #endif
1153 ! Check to see if expected value == actual value
1154 ! If not, print message and exit.
1155 SUBROUTINE test_check_error( expected, actual, str, file_str, line )
1156   IMPLICIT NONE
1157   INTEGER , INTENT (IN) :: expected
1158   INTEGER , INTENT (IN) :: actual
1159   CHARACTER*(*) str
1160   CHARACTER*(*) file_str
1161   INTEGER , INTENT (IN) :: line
1162   CHARACTER (LEN=512)   :: rc_str
1163   CHARACTER (LEN=512)   :: str_with_rc
1164   IF ( expected .ne. actual ) THEN
1165     WRITE (rc_str,*) '  Routine returned error code = ',actual
1166     str_with_rc = 'FAIL:  '//TRIM(str)//TRIM(rc_str)
1167     CALL wrf_error_fatal3( file_str, line, str_with_rc )
1168   ENDIF
1169 END SUBROUTINE test_check_error
1173 PROGRAM time_manager_test
1174   USE ESMF_Mod
1175   USE my_tests
1176   IMPLICIT NONE
1177   INTEGER :: rc
1179   PRINT *,'BEGIN TEST SUITE'
1181   CALL ESMF_Initialize( defaultCalendar=ESMF_CAL_GREGORIAN, rc=rc )
1182   CALL test_check_error( ESMF_SUCCESS, rc, &
1183                         'ESMF_Initialize() ', &
1184                         __FILE__ , &
1185                         __LINE__  )
1186 !  PRINT *,'DEBUG:  back from ESMF_Initialize(), rc = ',rc
1188 !  CALL test_print(  t_yy,  t_mm,  t_dd,  t_h,  t_m,  t_s, &
1189 !                   ti_yy, ti_mm, ti_dd, ti_h, ti_m, ti_s, &
1190 !                   res_str, testname )
1192   ! Print times
1193   ! "vanilla" tests
1194 !  PRINT *,'DEBUG:  calling 1st test_print()'
1195   CALL test_print( t_yy=2001,  t_mm=12,  t_dd=3,  t_h=1,  t_m=20,  t_s=10, &
1196     res_str='2001-12-03_01:20:10', testname='printT_1' )
1197 !  PRINT *,'DEBUG:  back from 1st test_print()'
1198   CALL test_print( t_yy=0,  t_mm=1,  t_dd=1,  t_h=0,  t_m=0,  t_s=0, &
1199     res_str='0000-01-01_00:00:00', testname='printT_2' )
1200   CALL test_print( t_yy=2003,  t_mm=12,  t_dd=30,  t_h=23,  t_m=59,  t_s=50, &
1201     res_str='2003-12-30_23:59:50', testname='printT_3' )
1202   CALL test_print( t_yy=2003,  t_mm=12,  t_dd=31,  t_h=23,  t_m=59,  t_s=50, &
1203     res_str='2003-12-31_23:59:50', testname='printT_4' )
1204   CALL test_print( t_yy=2004,  t_mm=12,  t_dd=30,  t_h=23,  t_m=59,  t_s=50, &
1205     res_str='2004-12-30_23:59:50', testname='printT_5' )
1206   CALL test_print( t_yy=2004,  t_mm=12,  t_dd=31,  t_h=23,  t_m=59,  t_s=50, &
1207     res_str='2004-12-31_23:59:50', testname='printT_6' )
1208 !$$$  NOTE that this fails -- need to fix up output string for negative year
1209 !  CALL test_print( t_yy=-2004,  t_mm=12,  t_dd=31,  t_h=23,  t_m=59,  t_s=50, &
1210 !    res_str='-2004-12-31_23:59:50', testname='printT_6' )
1212   ! these test default behavior of test harness
1213   CALL test_print( t_s=0, &
1214     res_str='0000-01-01_00:00:00', testname='printT_D1' )
1215   CALL test_print( t_yy=0, &
1216     res_str='0000-01-01_00:00:00', testname='printT_D2' )
1218   ! fractions
1219   CALL test_print( t_yy=2001,  t_mm=12,  t_dd=3,  t_h=1,  t_m=20,  t_s=10, &
1220     t_sn=1, t_sd=3, &
1221     res_str='2001-12-03_01:20:10+01/03', testname='printT_F1' )
1222   CALL test_print( t_yy=2001,  t_mm=12,  t_dd=3,  t_h=1,  t_m=20,  t_s=10, &
1223     t_sn=4, t_sd=3, &
1224     res_str='2001-12-03_01:20:11+01/03', testname='printT_F2' )
1225   CALL test_print( t_yy=2001,  t_mm=12,  t_dd=3,  t_h=1,  t_m=20,  t_s=10, &
1226     t_sn=12, t_sd=3, &
1227     res_str='2001-12-03_01:20:14', testname='printT_F3' )
1228   CALL test_print( t_yy=2001,  t_mm=12,  t_dd=3,  t_h=1,  t_m=20,  t_s=10, &
1229     t_sn=-1, t_sd=3, &
1230     res_str='2001-12-03_01:20:09+02/03', testname='printT_F4' )
1232   ! ERROR, MM out of range
1233 !$$$here...  fix so this just prints "ERROR:  <testname>" in failure case
1234 !$$$here...  also need "expect_fail" to reverse sense of PASS/FAIL message for 
1235 !$$$here...  tests that should fail
1236 !  CALL test_print( t_yy=2001,  t_mm=13,  t_dd=3,  t_h=1,  t_m=20,  t_s=10, &
1237 !    res_str='2002-01-03_01:20:10', testname='printT_E1', expect_error=.TRUE. )
1239   ! Print time intervals
1240   ! "vanilla" tests
1241   CALL test_print( ti_yy=0,  ti_mm=0,  ti_dd=0,  ti_h=0,  ti_m=0,  ti_s=0, &
1242     res_str='0000000000_000:000:000', testname='printTI_1' )
1243   CALL test_print( ti_yy=0,  ti_mm=0,  ti_dd=500,  ti_h=0,  ti_m=0,  ti_s=7270, &
1244     res_str='0000000500_002:001:010', testname='printTI_2' )
1246   ! these test default behavior of test harness
1247   CALL test_print( ti_s=0, &
1248     res_str='0000000000_000:000:000', testname='printTI_D1' )
1249   CALL test_print( ti_yy=0, &
1250     res_str='0000000000_000:000:000', testname='printTI_D2' )
1252   ! these test negative values
1253   CALL test_print( ti_yy=0000,  ti_mm=0,  ti_dd=-3,  ti_h=-1,  ti_m=-20,  ti_s=-10, &
1254     res_str='-0000000003_001:020:010', testname='printTI_N1' )
1256   ! these test mixed values
1257   CALL test_print( ti_yy=0000,  ti_mm=0,  ti_dd=-3,  ti_h=1,  ti_m=20,  ti_s=10, &
1258     res_str='-0000000002_022:039:050', testname='printTI_M1' )
1260   ! fractions
1261   CALL test_print( ti_yy=0000,  ti_mm=0,  ti_dd=3,  ti_h=1,  ti_m=20,  ti_s=10, &
1262     ti_sn=1, ti_sd=3, &
1263     res_str='0000000003_001:020:010+01/03', testname='printTI_F1' )
1264   CALL test_print( ti_yy=0000,  ti_mm=0,  ti_dd=3,  ti_h=1,  ti_m=20,  ti_s=10, &
1265     ti_sn=5, ti_sd=3, &
1266     res_str='0000000003_001:020:011+02/03', testname='printTI_F2' )
1267   CALL test_print( ti_yy=0000,  ti_mm=0,  ti_dd=-3,  ti_h=-1,  ti_m=-20,  ti_s=-10, &
1268     ti_sn=-1, ti_sd=3, &
1269     res_str='-0000000003_001:020:010-01/03', testname='printTI_F3' )
1270   CALL test_print( ti_yy=0000,  ti_mm=0,  ti_dd=-3,  ti_h=-1,  ti_m=-20,  ti_s=-10, &
1271     ti_sn=1, ti_sd=3, &
1272     res_str='-0000000003_001:020:009-02/03', testname='printTI_F4' )
1274   ! these test non-normalized values
1275 !  CALL test_print( ti_yy=2001,  ti_mm=1,  ti_dd=3,  ti_h=1,  ti_m=20,  ti_s=10, &
1276 !    res_str='02001-001-003_001:020:010', testname='printTI_NN1', expect_error=.TRUE. )
1277 !  CALL test_print( ti_yy=2001,  ti_mm=12,  ti_dd=3,  ti_h=1,  ti_m=20,  ti_s=10, &
1278 !    res_str='02002-000-003_001:020:010', testname='printTI_NN2', expect_error=.TRUE. )
1279 !  CALL test_print( ti_yy=2002,  ti_mm=5,  ti_dd=500,  ti_h=0,  ti_m=0,  ti_s=7270, &
1280 !    res_str='02002-005-500_002:001:010', testname='printTI_NN3', expect_error=.TRUE. )
1282   ! Addition tests
1283   ! ESMF_Time = ESMF_Time + ESMF_TimeInterval
1284   CALL test_arithmetic( add_op=.TRUE.,                                             &
1285      op1_t_yy=2001,  op1_t_mm=12,  op1_t_dd=3,  op1_t_h=1,  op1_t_m=20,  op1_t_s=10, &
1286     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=3, op2_ti_m=10, op2_ti_s=10, &
1287      res_t_yy=2001,  res_t_mm=12,  res_t_dd=3,  res_t_h=4,  res_t_m=30,  res_t_s=20, &
1288     testname='AddT_T_TI1' )
1289   CALL test_arithmetic( add_op=.TRUE.,                                             &
1290      op1_t_yy=2001,  op1_t_mm=12,  op1_t_dd=31,  op1_t_h=22,  op1_t_m=30,  op1_t_s=00, &
1291     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1292      res_t_yy=2002,  res_t_mm= 1,  res_t_dd=1,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1293     testname='AddT_T_TI2' )
1294   CALL test_arithmetic( add_op=.TRUE.,                                             &
1295      op1_t_yy=2003,  op1_t_mm=12,  op1_t_dd=31,  op1_t_h=22,  op1_t_m=30,  op1_t_s=00, &
1296     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1297      res_t_yy=2004,  res_t_mm= 1,  res_t_dd=1,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1298     testname='AddT_T_TI3' )
1299   CALL test_arithmetic( add_op=.TRUE.,                                             &
1300      op1_t_yy=2004,  op1_t_mm=12,  op1_t_dd=31,  op1_t_h=22,  op1_t_m=30,  op1_t_s=00, &
1301     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1302      res_t_yy=2005,  res_t_mm= 1,  res_t_dd=1,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1303     testname='AddT_T_TI4' )
1304   ! this case hung after the CCSM contribution
1305   CALL test_arithmetic( add_op=.TRUE.,                                             &
1306      op1_t_yy=2004,  op1_t_mm=12,  op1_t_dd=30,  op1_t_h=22,  op1_t_m=30,  op1_t_s=00, &
1307     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1308      res_t_yy=2004,  res_t_mm=12,  res_t_dd=31,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1309     testname='AddT_T_TI5' )
1310 ! NOTE:  CCSM folks need to decide what it means to add "1 month" to Feb. 29.  And all the 
1311 !        other very similar cases.  Then, write this unit test!  
1312 !  CALL test_arithmetic( add_op=.TRUE.,                                             &
1313 !     op1_t_yy=2004,  op1_t_mm=12,  op1_t_dd=31,  op1_t_h=22,  op1_t_m=30,  op1_t_s=00, &
1314 !    op2_ti_yy=   2, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1315 !     res_t_yy=2007,  res_t_mm= 1,  res_t_dd=1,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1316 !    testname='AddT_T_TI6' )
1317   CALL test_arithmetic( add_op=.TRUE.,                                             &
1318      op1_t_yy=2004,  op1_t_mm=12,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1319     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=365, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1320      res_t_yy=2005,  res_t_mm=12,  res_t_dd=30,  res_t_h=8,  res_t_m=40,  res_t_s=10, &
1321     testname='AddT_T_TI7' )
1322   CALL test_arithmetic( add_op=.TRUE.,                                             &
1323      op1_t_yy=2004,  op1_t_mm=12,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1324     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=367, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1325      res_t_yy=2006,  res_t_mm=01,  res_t_dd=01,  res_t_h=8,  res_t_m=40,  res_t_s=10, &
1326     testname='AddT_T_TI8' )
1327   CALL test_arithmetic( add_op=.TRUE.,                                             &
1328      op1_t_yy=2003,  op1_t_mm=12,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1329     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=365, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1330      res_t_yy=2004,  res_t_mm=12,  res_t_dd=29,  res_t_h=8,  res_t_m=40,  res_t_s=10, &
1331     testname='AddT_T_TI9' )
1332   CALL test_arithmetic( add_op=.TRUE.,                                             &
1333      op1_t_yy=2003,  op1_t_mm=12,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1334     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=366, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1335      res_t_yy=2004,  res_t_mm=12,  res_t_dd=30,  res_t_h=8,  res_t_m=40,  res_t_s=10, &
1336     testname='AddT_T_TI10' )
1337   CALL test_arithmetic( add_op=.TRUE.,                                             &
1338      op1_t_yy=2003,  op1_t_mm=12,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1339     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=367, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1340      res_t_yy=2004,  res_t_mm=12,  res_t_dd=31,  res_t_h=8,  res_t_m=40,  res_t_s=10, &
1341     testname='AddT_T_TI11' )
1342   CALL test_arithmetic( add_op=.TRUE.,                                             &
1343      op1_t_yy=2003,  op1_t_mm=12,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1344     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=368, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1345      res_t_yy=2005,  res_t_mm=01,  res_t_dd=01,  res_t_h=8,  res_t_m=40,  res_t_s=10, &
1346     testname='AddT_T_TI12' )
1347   CALL test_arithmetic( add_op=.TRUE.,                                             &
1348      op1_t_yy=2004,  op1_t_mm=03,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1349     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=365, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1350      res_t_yy=2005,  res_t_mm=03,  res_t_dd=30,  res_t_h=8,  res_t_m=40,  res_t_s=10, &
1351     testname='AddT_T_TI13' )
1352   CALL test_arithmetic( add_op=.TRUE.,                                             &
1353      op1_t_yy=2004,  op1_t_mm=03,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1354     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=365, op2_ti_h=22, op2_ti_m=10, op2_ti_s=10, &
1355      res_t_yy=2005,  res_t_mm=03,  res_t_dd=31,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1356     testname='AddT_T_TI14' )
1357   CALL test_arithmetic( add_op=.TRUE.,                                             &
1358      op1_t_yy=2004,  op1_t_mm=03,  op1_t_dd=30,  op1_t_h=4,  op1_t_m=30,  op1_t_s=00, &
1359     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=366, op2_ti_h=22, op2_ti_m=10, op2_ti_s=10, &
1360      res_t_yy=2005,  res_t_mm=04,  res_t_dd=01,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1361     testname='AddT_T_TI15' )
1362   ! ESMF_Time = ESMF_Time + ESMF_TimeInterval with fractions
1363   CALL test_arithmetic( add_op=.TRUE.,                                             &
1364      op1_t_yy=2004,  op1_t_mm=12,  op1_t_dd=31,  op1_t_h=22,  op1_t_m=30,  op1_t_s=00, &
1365      op1_t_sn=01,  op1_t_sd=03, &
1366     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1367     op2_ti_sn=01, op2_ti_sd=03, &
1368      res_t_yy=2005,  res_t_mm= 1,  res_t_dd=1,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1369      res_t_sn=02,  res_t_sd=03, &
1370     testname='AddT_T_TI_F1' )
1371   ! this should fail (and does)
1372 !  CALL test_arithmetic( add_op=.TRUE.,                                             &
1373 !     op1_t_yy=2004,  op1_t_mm=12,  op1_t_dd=31,  op1_t_h=22,  op1_t_m=30,  op1_t_s=00, &
1374 !     op1_t_sn=01,  op1_t_sd=03, &
1375 !    op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1376 !    op2_ti_sn=01, op2_ti_sd=03, &
1377 !     res_t_yy=2005,  res_t_mm= 1,  res_t_dd=1,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1378 !     res_t_sn=01,  res_t_sd=03, &
1379 !    testname='AddT_T_TI_F2' )
1380   ! ESMF_Time = ESMF_TimeInterval + ESMF_Time
1381   CALL test_arithmetic( add_op=.TRUE.,                                             &
1382     op1_ti_yy=   0, op1_ti_mm= 0, op1_ti_dd=0, op1_ti_h=3, op1_ti_m=10, op1_ti_s=10, &
1383      op2_t_yy=2001,  op2_t_mm=12,  op2_t_dd=3,  op2_t_h=1,  op2_t_m=20,  op2_t_s=10, &
1384      res_t_yy=2001,  res_t_mm=12,  res_t_dd=3,  res_t_h=4,  res_t_m=30,  res_t_s=20, &
1385     testname='AddT_TI_T1' )
1386   CALL test_arithmetic( add_op=.TRUE.,                                             &
1387     op1_ti_yy=   0, op1_ti_mm= 0, op1_ti_dd=0, op1_ti_h=4, op1_ti_m=10, op1_ti_s=10, &
1388      op2_t_yy=2001,  op2_t_mm=12,  op2_t_dd=31,  op2_t_h=22,  op2_t_m=30,  op2_t_s=00, &
1389      res_t_yy=2002,  res_t_mm= 1,  res_t_dd=1,  res_t_h=2,  res_t_m=40,  res_t_s=10, &
1390     testname='AddT_TI_T2' )
1391   ! ESMF_TimeInterval = ESMF_TimeInterval + ESMF_TimeInterval
1392   CALL test_arithmetic( add_op=.TRUE.,                                             &
1393     op1_ti_yy=0000, op1_ti_mm=00, op1_ti_dd=3, op1_ti_h=1, op1_ti_m=20, op1_ti_s=10, &
1394     op2_ti_yy=0000, op2_ti_mm=00, op2_ti_dd=1, op2_ti_h=1, op2_ti_m=10, op2_ti_s=10, &
1395     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=4, res_ti_h=2, res_ti_m=30, res_ti_s=20, &
1396     testname='AddTI_TI_TI1' )
1397   CALL test_arithmetic( add_op=.TRUE.,                                             &
1398     op1_ti_yy=0000, op1_ti_mm=00, op1_ti_dd=-3, op1_ti_h=-1, op1_ti_m=-20, op1_ti_s=-10, &
1399     op2_ti_yy=0000, op2_ti_mm=00, op2_ti_dd=1, op2_ti_h=1, op2_ti_m=10, op2_ti_s=10, &
1400     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=-2, res_ti_h=0, res_ti_m=-10, res_ti_s=00, &
1401     testname='AddTI_TI_TI2' )
1402   CALL test_arithmetic( add_op=.TRUE.,                                             &
1403     op1_ti_yy=0000, op1_ti_mm=00, op1_ti_dd=-3, op1_ti_h=-1, op1_ti_m=-20, op1_ti_s=-10, &
1404     op2_ti_yy=0000, op2_ti_mm=00, op2_ti_dd=-1, op2_ti_h=-1, op2_ti_m=-10, op2_ti_s=-10, &
1405     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=-4, res_ti_h=-2, res_ti_m=-30, res_ti_s=-20, &
1406     testname='AddTI_TI_TI3' )
1408   ! Subtraction tests
1409   ! ESMF_Time = ESMF_Time - ESMF_TimeInterval
1410   CALL test_arithmetic( add_op=.FALSE.,                                            &
1411      op1_t_yy=2001,  op1_t_mm=12,  op1_t_dd=3,  op1_t_h=1,  op1_t_m=20,  op1_t_s=10, &
1412     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=3, op2_ti_m=10, op2_ti_s=10, &
1413      res_t_yy=2001,  res_t_mm=12,  res_t_dd=2,  res_t_h=22, res_t_m=10,  res_t_s=0,  &
1414     testname='SubtractT_T_TI1' )
1415   CALL test_arithmetic( add_op=.FALSE.,                                            &
1416      op1_t_yy=2005,  op1_t_mm=1,   op1_t_dd=1,  op1_t_h=0,  op1_t_m=00,  op1_t_s=0,  &
1417     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=0, op2_ti_m=00, op2_ti_s=10, &
1418      res_t_yy=2004,  res_t_mm=12,  res_t_dd=31, res_t_h=23, res_t_m=59,  res_t_s=50, &
1419     testname='SubtractT_T_TI2' )
1420   CALL test_arithmetic( add_op=.FALSE.,                                            &
1421      op1_t_yy=2004,  op1_t_mm=1,   op1_t_dd=1,  op1_t_h=0,  op1_t_m=00,  op1_t_s=0,  &
1422     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=0, op2_ti_m=00, op2_ti_s=10, &
1423      res_t_yy=2003,  res_t_mm=12,  res_t_dd=31, res_t_h=23, res_t_m=59,  res_t_s=50, &
1424     testname='SubtractT_T_TI3' )
1425   CALL test_arithmetic( add_op=.FALSE.,                                            &
1426      op1_t_yy=2003,  op1_t_mm=1,   op1_t_dd=1,  op1_t_h=0,  op1_t_m=00,  op1_t_s=0,  &
1427     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=0, op2_ti_m=00, op2_ti_s=10, &
1428      res_t_yy=2002,  res_t_mm=12,  res_t_dd=31, res_t_h=23, res_t_m=59,  res_t_s=50, &
1429     testname='SubtractT_T_TI4' )
1430   CALL test_arithmetic( add_op=.FALSE.,                                             &
1431      op1_t_yy=2005,  op1_t_mm=04,  op1_t_dd=01,  op1_t_h=2,  op1_t_m=40,  op1_t_s=10, &
1432     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=366, op2_ti_h=22, op2_ti_m=10, op2_ti_s=10, &
1433      res_t_yy=2004,  res_t_mm=03,  res_t_dd=30,  res_t_h=4,  res_t_m=30,  res_t_s=00, &
1434     testname='SubtractT_T_TI5' )
1435   CALL test_arithmetic( add_op=.FALSE.,                                             &
1436      op1_t_yy=2006,  op1_t_mm=01,  op1_t_dd=01,  op1_t_h=8,  op1_t_m=40,  op1_t_s=10, &
1437     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=367, op2_ti_h=4, op2_ti_m=10, op2_ti_s=10, &
1438      res_t_yy=2004,  res_t_mm=12,  res_t_dd=30,  res_t_h=4,  res_t_m=30,  res_t_s=00, &
1439     testname='SubtractT_T_TI6' )
1440   ! ESMF_Time = ESMF_Time - ESMF_TimeInterval with fractions
1441   CALL test_arithmetic( add_op=.FALSE.,                                             &
1442      op1_t_yy=2005,  op1_t_mm=01,  op1_t_dd=01,  op1_t_h=00,  op1_t_m=00,  op1_t_s=00, &
1443      op1_t_sn=00,  op1_t_sd=00, &
1444     op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=0, op2_ti_m=00, op2_ti_s=01, &
1445     op2_ti_sn=01, op2_ti_sd=03, &
1446      res_t_yy=2004,  res_t_mm=12,  res_t_dd=31,  res_t_h=23,  res_t_m=59,  res_t_s=58, &
1447      res_t_sn=02,  res_t_sd=03, &
1448     testname='SubtractT_T_TI_F1' )
1449   ! ESMF_TimeInterval = ESMF_Time - ESMF_Time
1450   CALL test_arithmetic( add_op=.FALSE.,                                            &
1451      op1_t_yy=2001,  op1_t_mm=12,  op1_t_dd=3,  op1_t_h=1,  op1_t_m=20,  op1_t_s=10, &
1452      op2_t_yy=2001,  op2_t_mm=12,  op2_t_dd=1,  op2_t_h=1,  op2_t_m=10,  op2_t_s=10, &
1453     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=2, res_ti_h=0, res_ti_m=10, res_ti_s=0,  &
1454     testname='SubtractTI_T_T1' )
1455   CALL test_arithmetic( add_op=.FALSE.,                                            &
1456      op1_t_yy=2002,  op1_t_mm=1,   op1_t_dd=1,  op1_t_h=0,  op1_t_m=00,  op1_t_s=00, &
1457      op2_t_yy=2001,  op2_t_mm=12,  op2_t_dd=31, op2_t_h=23, op2_t_m=59,  op2_t_s=50, &
1458     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=0, res_ti_h=0, res_ti_m=00, res_ti_s=10, &
1459     testname='SubtractTI_T_T2' )
1460   CALL test_arithmetic( add_op=.FALSE.,                                            &
1461      op1_t_yy=2005,  op1_t_mm=1,   op1_t_dd=1,  op1_t_h=0,  op1_t_m=00,  op1_t_s=00, &
1462      op2_t_yy=2004,  op2_t_mm=12,  op2_t_dd=31, op2_t_h=23, op2_t_m=59,  op2_t_s=50, &
1463     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=0, res_ti_h=0, res_ti_m=00, res_ti_s=10, &
1464     testname='SubtractTI_T_T3' )
1465   CALL test_arithmetic( add_op=.FALSE.,                                            &
1466      op1_t_yy=2003,  op1_t_mm=03,  op1_t_dd=01, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1467      op2_t_yy=2003,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=23, op2_t_m=59,  op2_t_s=50, &
1468     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=0, res_ti_h=0, res_ti_m=00, res_ti_s=10, &
1469     testname='SubtractTI_T_T4' )
1470   CALL test_arithmetic( add_op=.FALSE.,                                            &
1471      op1_t_yy=2004,  op1_t_mm=03,  op1_t_dd=01, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1472      op2_t_yy=2004,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=23, op2_t_m=59,  op2_t_s=50, &
1473     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=1, res_ti_h=0, res_ti_m=00, res_ti_s=10, &
1474     testname='SubtractTI_T_T5' )
1475   CALL test_arithmetic( add_op=.FALSE.,                                            &
1476      op1_t_yy=2002,  op1_t_mm=02,  op1_t_dd=28, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1477      op2_t_yy=2002,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=00, op2_t_m=00,  op2_t_s=00, &
1478     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=0, res_ti_h=0, res_ti_m=00, res_ti_s=00, &
1479     testname='SubtractTI_T_T6' )
1480   CALL test_arithmetic( add_op=.FALSE.,                                            &
1481      op1_t_yy=2003,  op1_t_mm=02,  op1_t_dd=28, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1482      op2_t_yy=2002,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=00, op2_t_m=00,  op2_t_s=00, &
1483     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=365, res_ti_h=0, res_ti_m=00, res_ti_s=00, &
1484     testname='SubtractTI_T_T7' )
1485   CALL test_arithmetic( add_op=.FALSE.,                                            &
1486      op1_t_yy=2004,  op1_t_mm=02,  op1_t_dd=28, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1487      op2_t_yy=2003,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=00, op2_t_m=00,  op2_t_s=00, &
1488     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=365, res_ti_h=0, res_ti_m=00, res_ti_s=00, &
1489     testname='SubtractTI_T_T8' )
1490   CALL test_arithmetic( add_op=.FALSE.,                                            &
1491      op1_t_yy=2005,  op1_t_mm=02,  op1_t_dd=28, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1492      op2_t_yy=2004,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=00, op2_t_m=00,  op2_t_s=00, &
1493     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=366, res_ti_h=0, res_ti_m=00, res_ti_s=00, &
1494     testname='SubtractTI_T_T9' )
1495   CALL test_arithmetic( add_op=.FALSE.,                                            &
1496      op1_t_yy=2003,  op1_t_mm=03,  op1_t_dd=01, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1497      op2_t_yy=2002,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=00, op2_t_m=00,  op2_t_s=00, &
1498     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=366, res_ti_h=0, res_ti_m=00, res_ti_s=00, &
1499     testname='SubtractTI_T_T10' )
1500   CALL test_arithmetic( add_op=.FALSE.,                                            &
1501      op1_t_yy=2005,  op1_t_mm=03,  op1_t_dd=01, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1502      op2_t_yy=2004,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=00, op2_t_m=00,  op2_t_s=00, &
1503     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=367, res_ti_h=0, res_ti_m=00, res_ti_s=00, &
1504     testname='SubtractTI_T_T11' )
1505   CALL test_arithmetic( add_op=.FALSE.,                                            &
1506      op1_t_yy=2005,  op1_t_mm=03,  op1_t_dd=01, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1507      op2_t_yy=2004,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=23, op2_t_m=59,  op2_t_s=50, &
1508     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=366, res_ti_h=0, res_ti_m=00, res_ti_s=10, &
1509     testname='SubtractTI_T_T12' )
1510   CALL test_arithmetic( add_op=.FALSE.,                                            &
1511      op1_t_yy=2004,  op1_t_mm=02,  op1_t_dd=28, op1_t_h=23, op1_t_m=59,  op1_t_s=50, &
1512      op2_t_yy=2005,  op2_t_mm=03,  op2_t_dd=01, op2_t_h=00, op2_t_m=00,  op2_t_s=00, &
1513     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=-366, res_ti_h=0, res_ti_m=00, res_ti_s=-10, &
1514     testname='SubtractTI_T_T13' )
1515   CALL test_arithmetic( add_op=.FALSE.,                                            &
1516      op1_t_yy=-2002,  op1_t_mm=02,  op1_t_dd=28, op1_t_h=00, op1_t_m=00,  op1_t_s=00, &
1517      op2_t_yy=-2002,  op2_t_mm=02,  op2_t_dd=28, op2_t_h=00, op2_t_m=00,  op2_t_s=00, &
1518     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=0, res_ti_h=0, res_ti_m=00, res_ti_s=00, &
1519     testname='SubtractTI_T_T14' )
1520   ! ESMF_TimeInterval = ESMF_TimeInterval - ESMF_TimeInterval
1521   CALL test_arithmetic( add_op=.FALSE.,                                            &
1522     op1_ti_yy=0000, op1_ti_mm=00, op1_ti_dd=3, op1_ti_h=1, op1_ti_m=20, op1_ti_s=10, &
1523     op2_ti_yy=0000, op2_ti_mm=00, op2_ti_dd=1, op2_ti_h=1, op2_ti_m=10, op2_ti_s=10, &
1524     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=2, res_ti_h=0, res_ti_m=10, res_ti_s=0,  &
1525     testname='SubtractTI_TI_TI1' )
1526   CALL test_arithmetic( add_op=.FALSE.,                                            &
1527     op1_ti_yy=0000, op1_ti_mm=00, op1_ti_dd=3, op1_ti_h=1, op1_ti_m=20, op1_ti_s=10, &
1528     op2_ti_yy=0000, op2_ti_mm=00, op2_ti_dd=-1, op2_ti_h=-1, op2_ti_m=-10, op2_ti_s=-10, &
1529     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=4, res_ti_h=2, res_ti_m=30, res_ti_s=20,  &
1530     testname='SubtractTI_TI_TI2' )
1531   CALL test_arithmetic( add_op=.FALSE.,                                            &
1532     op1_ti_yy=0000, op1_ti_mm=00, op1_ti_dd=-1, op1_ti_h=-1, op1_ti_m=-10, op1_ti_s=-10, &
1533     op2_ti_yy=0000, op2_ti_mm=00, op2_ti_dd=-3, op2_ti_h=-1, op2_ti_m=-20, op2_ti_s=-10, &
1534     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=2, res_ti_h=0, res_ti_m=10, res_ti_s=00,  &
1535     testname='SubtractTI_TI_TI3' )
1536   ! Negative result ESMF_TimeInterval = ESMF_TimeInterval - ESMF_TimeInterval
1537   CALL test_arithmetic( add_op=.FALSE.,                                            &
1538     op1_ti_yy=0000, op1_ti_mm=00, op1_ti_dd=1, op1_ti_h=1, op1_ti_m=10, op1_ti_s=10, &
1539     op2_ti_yy=0000, op2_ti_mm=00, op2_ti_dd=3, op2_ti_h=1, op2_ti_m=20, op2_ti_s=10, &
1540     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=-2, res_ti_h=0, res_ti_m=-10, res_ti_s=0,  &
1541     testname='SubtractTI_TI_TIN1' )
1542   CALL test_arithmetic( add_op=.FALSE.,                                            &
1543     op1_ti_yy=0000, op1_ti_mm=00, op1_ti_dd=-1, op1_ti_h=-1, op1_ti_m=-10, op1_ti_s=-10, &
1544     op2_ti_yy=0000, op2_ti_mm=00, op2_ti_dd=3, op2_ti_h=1, op2_ti_m=20, op2_ti_s=10, &
1545     res_ti_yy=0000, res_ti_mm=00, res_ti_dd=-4, res_ti_h=-2, res_ti_m=-30, res_ti_s=-20,  &
1546     testname='SubtractTI_TI_TIN2' )
1548   ! Un-normalized ESMF_TimeInterval = ESMF_TimeInterval - ESMF_TimeInterval
1549   ! this is an error
1550 !  CALL test_arithmetic( add_op=.FALSE.,                                            &
1551 !    op1_ti_yy=2001, op1_ti_mm=11, op1_ti_dd=3, op1_ti_h=1, op1_ti_m=20, op1_ti_s=10, &
1552 !    op2_ti_yy=2001, op2_ti_mm=11, op2_ti_dd=1, op2_ti_h=1, op2_ti_m=10, op2_ti_s=10, &
1553 !    res_ti_yy=0000, res_ti_mm=00, res_ti_dd=2, res_ti_h=0, res_ti_m=10, res_ti_s=0,  &
1554 !    testname='SubtractTI_TI_TIU1', expect_error=.TRUE. )
1556   ! this one should FAIL, and does
1557 !  CALL test_arithmetic( add_op=.TRUE.,                                             &
1558 !     op1_t_yy=2001,  op1_t_mm=12,  op1_t_dd=3,  op1_t_h=1,  op1_t_m=20,  op1_t_s=10, &
1559 !    op2_ti_yy=   0, op2_ti_mm= 0, op2_ti_dd=0, op2_ti_h=3, op2_ti_m=10, op2_ti_s=10, &
1560 !     res_t_yy=2002,  res_t_mm=12,  res_t_dd=3,  res_t_h=4,  res_t_m=30,  res_t_s=20, &
1561 !    testname='AddTT1' )
1563   ! Multiplication tests
1564   ! ESMF_TimeInterval = ESMF_TimeInterval * INTEGER
1565   CALL test_arithmetic( multiply_op=.TRUE.,                &
1566     op1_ti_dd=3,  op1_ti_h=12,  op1_ti_m=18,  op1_ti_s=33, &
1567     op2_int=2,                                             &
1568     res_ti_dd=6,  res_ti_h=24, res_ti_m=37,  res_ti_s=06,  &
1569     testname='MultiplyTI_TI_INT1' )
1570   CALL test_arithmetic( multiply_op=.TRUE.,                &
1571     op1_ti_dd=350,  op1_ti_h=23,  op1_ti_m=50,  op1_ti_s=50, &
1572     op2_int=2,                                             &
1573     res_ti_dd=701,  res_ti_h=23, res_ti_m=41,  res_ti_s=40,&
1574     testname='MultiplyTI_TI_INT2' )
1575   CALL test_arithmetic( multiply_op=.TRUE.,                &
1576     op1_ti_s=01, op1_ti_sn=03, op1_ti_sd=04,               &
1577     op2_int=8,                                             &
1578     res_ti_s=14,                                           &
1579     testname='MultiplyTI_TI_INT3' )
1581   ! Division tests
1582   ! ESMF_TimeInterval = ESMF_TimeInterval / INTEGER
1583   CALL test_arithmetic( multiply_op=.FALSE.,               &
1584     op1_ti_dd=3,  op1_ti_h=12,  op1_ti_m=18,  op1_ti_s=33, &
1585     op2_int=3,                                             &
1586     res_ti_dd=1,  res_ti_h=04, res_ti_m=06,  res_ti_s=11,  &
1587     testname='DivideTI_TI_INT1' )
1588   CALL test_arithmetic( multiply_op=.FALSE.,               &
1589     op1_ti_dd=3,  op1_ti_h=12,  op1_ti_m=18,  op1_ti_s=33, &
1590     op2_int=4,                                             &
1591     res_ti_dd=0,  res_ti_h=21, res_ti_m=04,  res_ti_s=38,  &
1592     res_ti_sn=1,  res_ti_sd=4,                             &
1593     testname='DivideTI_TI_INT2' )
1594   CALL test_arithmetic( multiply_op=.FALSE.,               &
1595     op1_ti_s=01, op1_ti_sn=03, op1_ti_sd=04,               &
1596     op2_int=5,                                             &
1597     res_ti_s=0, res_ti_sn=7,  res_ti_sd=20,                &
1598     testname='DivideTI_TI_INT3' )
1599   ! INTEGER = ESMF_TimeInterval / ESMF_TimeInterval
1600   ! this operator truncates to whole integers
1601   CALL test_arithmetic( multiply_op=.FALSE.,               &
1602     op1_ti_dd=3,  op1_ti_h=12,  op1_ti_m=18,  op1_ti_s=33, &
1603     op2_ti_dd=3,  op2_ti_h=12,  op2_ti_m=18,  op2_ti_s=33, &
1604     res_int=1,                                             &
1605     testname='DivideINT_TI_TI1' )
1606   CALL test_arithmetic( multiply_op=.FALSE.,               &
1607     op1_ti_dd=6,  op1_ti_h=24,  op1_ti_m=36,  op1_ti_s=66, &
1608     op2_ti_dd=3,  op2_ti_h=12,  op2_ti_m=18,  op2_ti_s=33, &
1609     res_int=2,                                             &
1610     testname='DivideINT_TI_TI2' )
1611   CALL test_arithmetic( multiply_op=.FALSE.,               &
1612     op1_ti_dd=0,  op1_ti_h=00,  op1_ti_m=00,  op1_ti_s=00, &
1613     op2_ti_dd=3,  op2_ti_h=12,  op2_ti_m=18,  op2_ti_s=33, &
1614     res_int=0,                                             &
1615     testname='DivideINT_TI_TI3' )
1616   CALL test_arithmetic( multiply_op=.FALSE.,               &
1617     op1_ti_dd=1,  op1_ti_h=00,  op1_ti_m=00,  op1_ti_s=00, &
1618     op2_ti_dd=0,  op2_ti_h=01,  op2_ti_m=00,  op2_ti_s=00, &
1619     res_int=24,                                            &
1620     testname='DivideINT_TI_TI4' )
1621   CALL test_arithmetic( multiply_op=.FALSE.,               &
1622     op1_ti_dd=1,  op1_ti_h=00,  op1_ti_m=00,  op1_ti_s=00, &
1623     op2_ti_dd=0,  op2_ti_h=00,  op2_ti_m=01,  op2_ti_s=00, &
1624     res_int=1440,                                          &
1625     testname='DivideINT_TI_TI5' )
1626   CALL test_arithmetic( multiply_op=.FALSE.,               &
1627     op1_ti_dd=1,  op1_ti_h=00,  op1_ti_m=00,  op1_ti_s=00, &
1628     op2_ti_dd=0,  op2_ti_h=00,  op2_ti_m=00,  op2_ti_s=01, &
1629     res_int=86400,                                         &
1630     testname='DivideINT_TI_TI6' )
1631   ! rounding
1632   CALL test_arithmetic( multiply_op=.FALSE.,               &
1633     op1_ti_dd=0,  op1_ti_h=00,  op1_ti_m=00,  op1_ti_s=03, &
1634     op2_ti_dd=0,  op2_ti_h=00,  op2_ti_m=00,  op2_ti_s=02, &
1635     res_int=1,                                             &
1636     testname='DivideINT_TI_TIR1' )
1637   CALL test_arithmetic( multiply_op=.FALSE.,               &
1638     op1_ti_dd=1,  op1_ti_h=00,  op1_ti_m=00,  op1_ti_s=02, &
1639     op2_ti_dd=1,  op2_ti_h=00,  op2_ti_m=00,  op2_ti_s=03, &
1640     res_int=0,                                             &
1641     testname='DivideINT_TI_TIR2' )
1642   ! fractional operands
1643   CALL test_arithmetic( multiply_op=.FALSE.,               &
1644     op1_ti_m=00,  op1_ti_s=00, op1_ti_sn=03, op1_ti_sd=04, &
1645     op2_ti_m=00,  op2_ti_s=00, op2_ti_sn=03, op2_ti_sd=04, &
1646     res_int=1,                                             &
1647     testname='DivideINT_TI_TIF1' )
1648   CALL test_arithmetic( multiply_op=.FALSE.,               &
1649     op1_ti_m=00,  op1_ti_s=00, op1_ti_sn=06, op1_ti_sd=08, &
1650     op2_ti_m=00,  op2_ti_s=00, op2_ti_sn=03, op2_ti_sd=04, &
1651     res_int=1,                                             &
1652     testname='DivideINT_TI_TIF2' )
1653   CALL test_arithmetic( multiply_op=.FALSE.,               &
1654     op1_ti_m=00,  op1_ti_s=00, op1_ti_sn=03, op1_ti_sd=04, &
1655     op2_ti_m=00,  op2_ti_s=00, op2_ti_sn=04, op2_ti_sd=03, &
1656     res_int=0,                                             &
1657     testname='DivideINT_TI_TIF3' )
1658   CALL test_arithmetic( multiply_op=.FALSE.,               &
1659     op1_ti_m=00,  op1_ti_s=02, op1_ti_sn=03, op1_ti_sd=04, &
1660     op2_ti_m=00,  op2_ti_s=01, op2_ti_sn=01, op2_ti_sd=03, &
1661     res_int=2,                                             &
1662     testname='DivideINT_TI_TIF4' )
1663   ! negative operands
1664   CALL test_arithmetic( multiply_op=.FALSE.,               &
1665     op1_ti_dd=-6,  op1_ti_h=-24,  op1_ti_m=-36,  op1_ti_s=-66, &
1666     op2_ti_dd=3,  op2_ti_h=12,  op2_ti_m=18,  op2_ti_s=33, &
1667     res_int=-2,                                             &
1668     testname='DivideINT_TI_TIN1' )
1669   CALL test_arithmetic( multiply_op=.FALSE.,               &
1670     op1_ti_dd=6,  op1_ti_h=24,  op1_ti_m=36,  op1_ti_s=66, &
1671     op2_ti_dd=-3,  op2_ti_h=-12,  op2_ti_m=-18,  op2_ti_s=-33, &
1672     res_int=-2,                                             &
1673     testname='DivideINT_TI_TIN2' )
1674   CALL test_arithmetic( multiply_op=.FALSE.,               &
1675     op1_ti_dd=-6,  op1_ti_h=-24,  op1_ti_m=-36,  op1_ti_s=-66, &
1676     op2_ti_dd=-3,  op2_ti_h=-12,  op2_ti_m=-18,  op2_ti_s=-33, &
1677     res_int=2,                                             &
1678     testname='DivideINT_TI_TIN3' )
1680 !$$$here...  modify these to add self-test PASS/FAIL output
1681   CALL test_clock_advance(                                                    &
1682     start_yy=2002, start_mm=12, start_dd=27, start_h=3, start_m=0, start_s=0, &
1683      stop_yy=2002,  stop_mm=12,  stop_dd=28,  stop_h=8,  stop_m=0,  stop_s=0, &
1684     timestep_d=0, timestep_h=0, timestep_m=0, timestep_s=600,                 &
1685     testname="SimpleClockAdvance" )
1687   CALL test_clock_advance(                                                    &
1688     start_yy=2003, start_mm=12, start_dd=29, start_h=9, start_m=0, start_s=0, &
1689      stop_yy=2004,  stop_mm=1,   stop_dd=2,   stop_h=9,  stop_m=0,  stop_s=0, &
1690     timestep_d=0, timestep_h=0, timestep_m=0, timestep_s=3600,                &
1691     testname="StdYearClockAdvance", increment_S=10 )
1693   CALL test_clock_advance(                                                    &
1694     start_yy=2004, start_mm=12, start_dd=29, start_h=9, start_m=0, start_s=0, &
1695      stop_yy=2005,  stop_mm=1,   stop_dd=2,   stop_h=9,  stop_m=0,  stop_s=0, &
1696     timestep_d=0, timestep_h=0, timestep_m=0, timestep_s=3600,                &
1697     testname="LeapYearClockAdvance", increment_S=10 )
1699   ! NRCM domain 3 case:  120 seconds / 9 
1700   ! 18 timesteps through end of leap year
1701   CALL test_clock_advance(                                                    &
1702     start_yy=2004, start_mm=12, start_dd=31, start_h=23, start_m=58, start_s=0,&
1703      stop_yy=2005,  stop_mm=1,   stop_dd=1,   stop_h=0,  stop_m=2,  stop_s=0, &
1704     timestep_d=0, timestep_h=0, timestep_m=0, timestep_s=13,                  &
1705     timestep_sn=1, timestep_sd=3,                                             &
1706     testname="LeapYearFractionClockAdvance",                                  &
1707     increment_S=1, increment_Sn=1, increment_Sd=3 )
1709   CALL ESMF_Finalize( rc=rc )
1710   CALL test_check_error( ESMF_SUCCESS, rc, &
1711                         'ESMF_Finalize() ', &
1712                         __FILE__ , &
1713                         __LINE__  )
1715   PRINT *,'END TEST SUITE'
1717 END PROGRAM time_manager_test