set_timekeeping.F

References to this file elsewhere.
1 SUBROUTINE Setup_Timekeeping ( grid )
2    USE module_domain
3    USE module_configure
4    USE module_utility
5    IMPLICIT NONE
6    TYPE(domain), POINTER :: grid
7 ! Local
8    TYPE(WRFU_TimeInterval) :: begin_time, end_time, zero_time, one_minute, one_hour, padding_interval
9    TYPE(WRFU_TimeInterval) :: interval, run_length
10    TYPE(WRFU_Time) :: startTime, stopTime
11    TYPE(WRFU_TimeInterval) :: stepTime
12    INTEGER :: start_year,start_month,start_day,start_hour,start_minute,start_second
13    INTEGER :: end_year,end_month,end_day,end_hour,end_minute,end_second
14 #ifdef MOVE_NESTS
15    INTEGER :: vortex_interval
16 #endif
17 
18    INTEGER :: history_interval  , restart_interval  ,  &
19               history_interval_mo, restart_interval_mo,  &
20               history_interval_d, restart_interval_d,  &
21               history_interval_h, restart_interval_h,  &
22               history_interval_m, restart_interval_m,  &
23               history_interval_s, restart_interval_s
24 
25    INTEGER :: auxhist1_interval  , auxhist2_interval  , auxhist3_interval  , &
26               auxhist1_interval_mo, auxhist2_interval_mo, auxhist3_interval_mo, &
27               auxhist1_interval_d, auxhist2_interval_d, auxhist3_interval_d, &
28               auxhist1_interval_h, auxhist2_interval_h, auxhist3_interval_h, &
29               auxhist1_interval_m, auxhist2_interval_m, auxhist3_interval_m, &
30               auxhist1_interval_s, auxhist2_interval_s, auxhist3_interval_s
31 
32    INTEGER :: auxhist4_interval  , auxhist5_interval,   &
33               auxhist4_interval_mo, auxhist5_interval_mo, &
34               auxhist4_interval_d, auxhist5_interval_d, &
35               auxhist4_interval_h, auxhist5_interval_h, &
36               auxhist4_interval_m, auxhist5_interval_m, &
37               auxhist4_interval_s, auxhist5_interval_s
38 
39    INTEGER :: auxhist6_interval  , auxhist7_interval  , auxhist8_interval  , &
40               auxhist6_interval_mo, auxhist7_interval_mo, auxhist8_interval_mo, &
41               auxhist6_interval_d, auxhist7_interval_d, auxhist8_interval_d, &
42               auxhist6_interval_h, auxhist7_interval_h, auxhist8_interval_h, &
43               auxhist6_interval_m, auxhist7_interval_m, auxhist8_interval_m, &
44               auxhist6_interval_s, auxhist7_interval_s, auxhist8_interval_s
45 
46    INTEGER :: auxhist9_interval  , auxhist10_interval  , auxhist11_interval  , &
47               auxhist9_interval_mo, auxhist10_interval_mo, auxhist11_interval_mo, &
48               auxhist9_interval_d, auxhist10_interval_d, auxhist11_interval_d, &
49               auxhist9_interval_h, auxhist10_interval_h, auxhist11_interval_h, &
50               auxhist9_interval_m, auxhist10_interval_m, auxhist11_interval_m, &
51               auxhist9_interval_s, auxhist10_interval_s, auxhist11_interval_s
52 
53    INTEGER :: auxinput1_interval  , auxinput2_interval  , auxinput3_interval  , &
54               auxinput1_interval_mo, auxinput2_interval_mo, auxinput3_interval_mo, &
55               auxinput1_interval_d, auxinput2_interval_d, auxinput3_interval_d, &
56               auxinput1_interval_h, auxinput2_interval_h, auxinput3_interval_h, &
57               auxinput1_interval_m, auxinput2_interval_m, auxinput3_interval_m, &
58               auxinput1_interval_s, auxinput2_interval_s, auxinput3_interval_s
59 
60    INTEGER :: auxinput4_interval  , auxinput5_interval  , &
61               auxinput4_interval_mo, auxinput5_interval_mo, &
62               auxinput4_interval_d, auxinput5_interval_d, &
63               auxinput4_interval_h, auxinput5_interval_h, &
64               auxinput4_interval_m, auxinput5_interval_m, &
65               auxinput4_interval_s, auxinput5_interval_s
66 
67    INTEGER :: auxinput6_interval  , auxinput7_interval  , auxinput8_interval  , &
68               auxinput6_interval_mo, auxinput7_interval_mo, auxinput8_interval_mo, &
69               auxinput6_interval_d, auxinput7_interval_d, auxinput8_interval_d, &
70               auxinput6_interval_h, auxinput7_interval_h, auxinput8_interval_h, &
71               auxinput6_interval_m, auxinput7_interval_m, auxinput8_interval_m, &
72               auxinput6_interval_s, auxinput7_interval_s, auxinput8_interval_s
73 
74    INTEGER :: auxinput9_interval  , gfdda_interval  , auxinput11_interval  , &
75               auxinput9_interval_mo, gfdda_interval_mo, auxinput11_interval_mo, &
76               auxinput9_interval_d, gfdda_interval_d, auxinput11_interval_d, &
77               auxinput9_interval_h, gfdda_interval_h, auxinput11_interval_h, &
78               auxinput9_interval_m, gfdda_interval_m, auxinput11_interval_m, &
79               auxinput9_interval_s, gfdda_interval_s, auxinput11_interval_s
80 
81    INTEGER :: history_begin  , restart_begin  ,  &
82               history_begin_y, restart_begin_y,  &
83               history_begin_mo, restart_begin_mo,  &
84               history_begin_d, restart_begin_d,  &
85               history_begin_h, restart_begin_h,  &
86               history_begin_m, restart_begin_m,  &
87               history_begin_s, restart_begin_s
88 
89    INTEGER :: auxhist1_begin  , auxhist2_begin  , auxhist3_begin  , &
90               auxhist1_begin_y, auxhist2_begin_y, auxhist3_begin_y, &
91               auxhist1_begin_mo, auxhist2_begin_mo, auxhist3_begin_mo, &
92               auxhist1_begin_d, auxhist2_begin_d, auxhist3_begin_d, &
93               auxhist1_begin_h, auxhist2_begin_h, auxhist3_begin_h, &
94               auxhist1_begin_m, auxhist2_begin_m, auxhist3_begin_m, &
95               auxhist1_begin_s, auxhist2_begin_s, auxhist3_begin_s
96 
97    INTEGER :: auxhist4_begin  , auxhist5_begin,   &
98               auxhist4_begin_y, auxhist5_begin_y, &
99               auxhist4_begin_mo, auxhist5_begin_mo, &
100               auxhist4_begin_d, auxhist5_begin_d, &
101               auxhist4_begin_h, auxhist5_begin_h, &
102               auxhist4_begin_m, auxhist5_begin_m, &
103               auxhist4_begin_s, auxhist5_begin_s
104 
105    INTEGER :: auxhist6_begin  , auxhist7_begin  , auxhist8_begin  , &
106               auxhist6_begin_y, auxhist7_begin_y, auxhist8_begin_y, &
107               auxhist6_begin_mo, auxhist7_begin_mo, auxhist8_begin_mo, &
108               auxhist6_begin_d, auxhist7_begin_d, auxhist8_begin_d, &
109               auxhist6_begin_h, auxhist7_begin_h, auxhist8_begin_h, &
110               auxhist6_begin_m, auxhist7_begin_m, auxhist8_begin_m, &
111               auxhist6_begin_s, auxhist7_begin_s, auxhist8_begin_s
112 
113    INTEGER :: auxhist9_begin  , auxhist10_begin  , auxhist11_begin  , &
114               auxhist9_begin_y, auxhist10_begin_y, auxhist11_begin_y, &
115               auxhist9_begin_mo, auxhist10_begin_mo, auxhist11_begin_mo, &
116               auxhist9_begin_d, auxhist10_begin_d, auxhist11_begin_d, &
117               auxhist9_begin_h, auxhist10_begin_h, auxhist11_begin_h, &
118               auxhist9_begin_m, auxhist10_begin_m, auxhist11_begin_m, &
119               auxhist9_begin_s, auxhist10_begin_s, auxhist11_begin_s
120 
121    INTEGER :: inputout_begin  ,  inputout_end,    inputout_interval ,    &
122               inputout_begin_y,  inputout_end_y,  inputout_interval_y ,    &
123               inputout_begin_mo, inputout_end_mo, inputout_interval_mo ,   &
124               inputout_begin_d,  inputout_end_d,  inputout_interval_d ,    &
125               inputout_begin_h,  inputout_end_h,  inputout_interval_h ,    &
126               inputout_begin_m,  inputout_end_m,  inputout_interval_m ,    &
127               inputout_begin_s,  inputout_end_s,  inputout_interval_s
128 
129    INTEGER :: auxinput1_begin  , auxinput2_begin  , auxinput3_begin  , &
130               auxinput1_begin_y, auxinput2_begin_y, auxinput3_begin_y, &
131               auxinput1_begin_mo, auxinput2_begin_mo, auxinput3_begin_mo, &
132               auxinput1_begin_d, auxinput2_begin_d, auxinput3_begin_d, &
133               auxinput1_begin_h, auxinput2_begin_h, auxinput3_begin_h, &
134               auxinput1_begin_m, auxinput2_begin_m, auxinput3_begin_m, &
135               auxinput1_begin_s, auxinput2_begin_s, auxinput3_begin_s
136 
137    INTEGER :: auxinput4_begin  , auxinput5_begin  , &
138               auxinput4_begin_y, auxinput5_begin_y, &
139               auxinput4_begin_mo, auxinput5_begin_mo, &
140               auxinput4_begin_d, auxinput5_begin_d, &
141               auxinput4_begin_h, auxinput5_begin_h, &
142               auxinput4_begin_m, auxinput5_begin_m, &
143               auxinput4_begin_s, auxinput5_begin_s
144 
145    INTEGER :: auxinput6_begin  , auxinput7_begin  , auxinput8_begin  , &
146               auxinput6_begin_y, auxinput7_begin_y, auxinput8_begin_y, &
147               auxinput6_begin_mo, auxinput7_begin_mo, auxinput8_begin_mo, &
148               auxinput6_begin_d, auxinput7_begin_d, auxinput8_begin_d, &
149               auxinput6_begin_h, auxinput7_begin_h, auxinput8_begin_h, &
150               auxinput6_begin_m, auxinput7_begin_m, auxinput8_begin_m, &
151               auxinput6_begin_s, auxinput7_begin_s, auxinput8_begin_s
152 
153    INTEGER :: auxinput9_begin  , gfdda_begin  , auxinput11_begin  , &
154               auxinput9_begin_y, gfdda_begin_y, auxinput11_begin_y, &
155               auxinput9_begin_mo, gfdda_begin_mo, auxinput11_begin_mo, &
156               auxinput9_begin_d, gfdda_begin_d, auxinput11_begin_d, &
157               auxinput9_begin_h, gfdda_begin_h, auxinput11_begin_h, &
158               auxinput9_begin_m, gfdda_begin_m, auxinput11_begin_m, &
159               auxinput9_begin_s, gfdda_begin_s, auxinput11_begin_s
160 
161    INTEGER :: history_end  , restart_end  ,  &
162               history_end_y, restart_end_y,  &
163               history_end_mo, restart_end_mo,  &
164               history_end_d, restart_end_d,  &
165               history_end_h, restart_end_h,  &
166               history_end_m, restart_end_m,  &
167               history_end_s, restart_end_s
168 
169    INTEGER :: auxhist1_end  , auxhist2_end  , auxhist3_end  , &
170               auxhist1_end_y, auxhist2_end_y, auxhist3_end_y, &
171               auxhist1_end_mo, auxhist2_end_mo, auxhist3_end_mo, &
172               auxhist1_end_d, auxhist2_end_d, auxhist3_end_d, &
173               auxhist1_end_h, auxhist2_end_h, auxhist3_end_h, &
174               auxhist1_end_m, auxhist2_end_m, auxhist3_end_m, &
175               auxhist1_end_s, auxhist2_end_s, auxhist3_end_s
176 
177    INTEGER :: auxhist4_end  , auxhist5_end,   &
178               auxhist4_end_y, auxhist5_end_y, &
179               auxhist4_end_mo, auxhist5_end_mo, &
180               auxhist4_end_d, auxhist5_end_d, &
181               auxhist4_end_h, auxhist5_end_h, &
182               auxhist4_end_m, auxhist5_end_m, &
183               auxhist4_end_s, auxhist5_end_s
184 
185    INTEGER :: auxhist6_end  , auxhist7_end  , auxhist8_end  , &
186               auxhist6_end_y, auxhist7_end_y, auxhist8_end_y, &
187               auxhist6_end_mo, auxhist7_end_mo, auxhist8_end_mo, &
188               auxhist6_end_d, auxhist7_end_d, auxhist8_end_d, &
189               auxhist6_end_h, auxhist7_end_h, auxhist8_end_h, &
190               auxhist6_end_m, auxhist7_end_m, auxhist8_end_m, &
191               auxhist6_end_s, auxhist7_end_s, auxhist8_end_s
192 
193    INTEGER :: auxhist9_end  , auxhist10_end  , auxhist11_end  , &
194               auxhist9_end_y, auxhist10_end_y, auxhist11_end_y, &
195               auxhist9_end_mo, auxhist10_end_mo, auxhist11_end_mo, &
196               auxhist9_end_d, auxhist10_end_d, auxhist11_end_d, &
197               auxhist9_end_h, auxhist10_end_h, auxhist11_end_h, &
198               auxhist9_end_m, auxhist10_end_m, auxhist11_end_m, &
199               auxhist9_end_s, auxhist10_end_s, auxhist11_end_s
200 
201    INTEGER :: auxinput1_end  , auxinput2_end  , auxinput3_end  , &
202               auxinput1_end_y, auxinput2_end_y, auxinput3_end_y, &
203               auxinput1_end_mo, auxinput2_end_mo, auxinput3_end_mo, &
204               auxinput1_end_d, auxinput2_end_d, auxinput3_end_d, &
205               auxinput1_end_h, auxinput2_end_h, auxinput3_end_h, &
206               auxinput1_end_m, auxinput2_end_m, auxinput3_end_m, &
207               auxinput1_end_s, auxinput2_end_s, auxinput3_end_s
208 
209    INTEGER :: auxinput4_end  , auxinput5_end  , &
210               auxinput4_end_y, auxinput5_end_y, &
211               auxinput4_end_mo, auxinput5_end_mo, &
212               auxinput4_end_d, auxinput5_end_d, &
213               auxinput4_end_h, auxinput5_end_h, &
214               auxinput4_end_m, auxinput5_end_m, &
215               auxinput4_end_s, auxinput5_end_s
216 
217    INTEGER :: auxinput6_end  , auxinput7_end  , auxinput8_end  , &
218               auxinput6_end_y, auxinput7_end_y, auxinput8_end_y, &
219               auxinput6_end_mo, auxinput7_end_mo, auxinput8_end_mo, &
220               auxinput6_end_d, auxinput7_end_d, auxinput8_end_d, &
221               auxinput6_end_h, auxinput7_end_h, auxinput8_end_h, &
222               auxinput6_end_m, auxinput7_end_m, auxinput8_end_m, &
223               auxinput6_end_s, auxinput7_end_s, auxinput8_end_s
224 
225    INTEGER :: auxinput9_end  , gfdda_end  , auxinput11_end  , &
226               auxinput9_end_y, gfdda_end_y, auxinput11_end_y, &
227               auxinput9_end_mo, gfdda_end_mo, auxinput11_end_mo, &
228               auxinput9_end_d, gfdda_end_d, auxinput11_end_d, &
229               auxinput9_end_h, gfdda_end_h, auxinput11_end_h, &
230               auxinput9_end_m, gfdda_end_m, auxinput11_end_m, &
231               auxinput9_end_s, gfdda_end_s, auxinput11_end_s
232 
233    INTEGER :: grid_fdda
234 
235    INTEGER :: run_days, run_hours, run_minutes, run_seconds
236    INTEGER :: time_step, time_step_fract_num, time_step_fract_den
237    INTEGER :: rc
238    REAL    :: dt
239 
240    CALL WRFU_TimeIntervalSet ( zero_time, rc=rc )
241    CALL wrf_check_error( WRFU_SUCCESS, rc, &
242                          'WRFU_TimeIntervalSet(zero_time) FAILED', &
243                          __FILE__ , &
244                          __LINE__  )
245    CALL WRFU_TimeIntervalSet ( one_minute, M=1, rc=rc )
246    CALL wrf_check_error( WRFU_SUCCESS, rc, &
247                          'WRFU_TimeIntervalSet(one_minute) FAILED', &
248                          __FILE__ , &
249                          __LINE__  )
250    CALL WRFU_TimeIntervalSet ( one_hour, H=1, rc=rc )
251    CALL wrf_check_error( WRFU_SUCCESS, rc, &
252                          'WRFU_TimeIntervalSet(one_hour) FAILED', &
253                          __FILE__ , &
254                          __LINE__  )
255 
256    CALL nl_get_start_year(grid%id,start_year)
257    CALL nl_get_start_month(grid%id,start_month)
258    CALL nl_get_start_day(grid%id,start_day)
259    CALL nl_get_start_hour(grid%id,start_hour)
260    CALL nl_get_start_minute(grid%id,start_minute)
261    CALL nl_get_start_second(grid%id,start_second)
262    CALL WRFU_TimeSet(startTime, YY=start_year, MM=start_month, DD=start_day, &
263                                 H=start_hour, M=start_minute, S=start_second,&
264                                       rc=rc)
265    CALL wrf_check_error( WRFU_SUCCESS, rc, &
266                          'WRFU_TimeSet(startTime) FAILED', &
267                          __FILE__ , &
268                          __LINE__  )
269    CALL nl_get_run_days(1,run_days)
270    CALL nl_get_run_hours(1,run_hours)
271    CALL nl_get_run_minutes(1,run_minutes)
272    CALL nl_get_run_seconds(1,run_seconds)
273 
274    IF ( grid%id .EQ. head_grid%id .AND. &
275         ( run_days .gt. 0 .or. run_hours .gt. 0 .or. run_minutes .gt. 0 .or. run_seconds .gt. 0 )) THEN
276      CALL WRFU_TimeIntervalSet ( run_length , D=run_days, H=run_hours, M=run_minutes, S=run_seconds, rc=rc )
277      CALL wrf_check_error( WRFU_SUCCESS, rc, &
278                            'WRFU_TimeIntervalSet(run_length) FAILED', &
279                            __FILE__ , &
280                            __LINE__  )
281      stopTime = startTime + run_length
282    ELSE
283      CALL nl_get_end_year(grid%id,end_year)
284      CALL nl_get_end_month(grid%id,end_month)
285      CALL nl_get_end_day(grid%id,end_day)
286      CALL nl_get_end_hour(grid%id,end_hour)
287      CALL nl_get_end_minute(grid%id,end_minute)
288      CALL nl_get_end_second(grid%id,end_second)
289      CALL WRFU_TimeSet(stopTime, YY=end_year, MM=end_month, DD=end_day, &
290                                  H=end_hour, M=end_minute, S=end_second,&
291                                  rc=rc )
292      CALL wrf_check_error( WRFU_SUCCESS, rc, &
293                            'WRFU_TimeSet(stopTime) FAILED', &
294                            __FILE__ , &
295                            __LINE__  )
296      run_length = stopTime - startTime
297    ENDIF
298    IF ( run_length .GT. zero_time ) THEN
299      padding_interval = one_hour
300    ELSE
301      padding_interval = zero_time - one_hour
302    ENDIF
303 
304    IF ( grid%id .EQ. head_grid%id ) THEN
305       CALL nl_get_time_step ( 1, time_step )
306       CALL nl_get_time_step_fract_num( 1, time_step_fract_num )
307       CALL nl_get_time_step_fract_den( 1, time_step_fract_den )
308       dt = real(time_step) + real(time_step_fract_num) / real(time_step_fract_den)
309       CALL nl_set_dt( grid%id, dt )
310       grid%dt = dt
311       CALL WRFU_TimeIntervalSet(stepTime, S=time_step, Sn=time_step_fract_num, Sd=time_step_fract_den, rc=rc)
312       CALL wrf_check_error( WRFU_SUCCESS, rc, &
313                             'WRFU_TimeIntervalSet(stepTime) FAILED', &
314                             __FILE__ , &
315                             __LINE__  )
316    ELSE
317       stepTime = domain_get_time_step( grid%parents(1)%ptr ) / &
318                  grid%parent_time_step_ratio
319       grid%dt = grid%parents(1)%ptr%dt / grid%parent_time_step_ratio
320       CALL nl_set_dt( grid%id, grid%dt )
321    ENDIF
322 
323    ! create grid%domain_clock and associated state
324    CALL domain_clock_create( grid, TimeStep= stepTime,  &
325                                    StartTime=startTime, &
326                                    StopTime= stopTime )
327    CALL domain_clockprint ( 150, grid, &
328           'DEBUG setup_timekeeping():  clock after creation,' )
329 
330    ! Set default value for SIMULATION_START_DATE.  
331    ! This is overwritten later in input_wrf(), if needed.  
332    IF ( grid%id .EQ. head_grid%id ) THEN
333       CALL nl_set_simulation_start_year   ( 1 , start_year   )
334       CALL nl_set_simulation_start_month  ( 1 , start_month  )
335       CALL nl_set_simulation_start_day    ( 1 , start_day    )
336       CALL nl_set_simulation_start_hour   ( 1 , start_hour   )
337       CALL nl_set_simulation_start_minute ( 1 , start_minute )
338       CALL nl_set_simulation_start_second ( 1 , start_second )
339    ENDIF
340 
341 ! HISTORY INTERVAL
342 ! history_interval is left there (and means minutes) for consistency, but 
343 ! history_interval_m will take precedence if specified
344 
345    CALL nl_get_history_interval( grid%id, history_interval )   ! same as minutes
346    CALL nl_get_history_interval_mo( grid%id, history_interval_mo )
347    CALL nl_get_history_interval_d( grid%id, history_interval_d )
348    CALL nl_get_history_interval_h( grid%id, history_interval_h )
349    CALL nl_get_history_interval_m( grid%id, history_interval_m )
350    CALL nl_get_history_interval_s( grid%id, history_interval_s )
351    IF ( history_interval_m .EQ. 0 ) history_interval_m = history_interval
352 
353    IF ( MAX( history_interval_mo, history_interval_d,   &
354              history_interval_h, history_interval_m , history_interval_s   ) .GT. 0 ) THEN
355      CALL WRFU_TimeIntervalSet( interval, MM=history_interval_mo, D=history_interval_d, &
356                                           H=history_interval_h, M=history_interval_m, S=history_interval_s, rc=rc )
357      CALL wrf_check_error( WRFU_SUCCESS, rc, &
358                            'WRFU_TimeIntervalSet(history_interval) FAILED', &
359                            __FILE__ , &
360                            __LINE__  )
361    ELSE
362      interval = run_length + padding_interval
363    ENDIF
364 
365    CALL nl_get_history_begin_y( grid%id, history_begin_y )
366    CALL nl_get_history_begin_mo( grid%id, history_begin_mo )
367    CALL nl_get_history_begin_d( grid%id, history_begin_d )
368    CALL nl_get_history_begin_h( grid%id, history_begin_h )
369    CALL nl_get_history_begin_m( grid%id, history_begin_m )
370    CALL nl_get_history_begin_s( grid%id, history_begin_s )
371    IF ( MAX( history_begin_y, history_begin_mo, history_begin_d,   &
372              history_begin_h, history_begin_m , history_begin_s   ) .GT. 0 ) THEN
373       CALL WRFU_TimeIntervalSet( begin_time , MM=history_begin_mo, D=history_begin_d, &
374                                               H=history_begin_h, M=history_begin_m, S=history_begin_s, rc=rc )
375       CALL wrf_check_error( WRFU_SUCCESS, rc, &
376                             'WRFU_TimeIntervalSet(history_begin) FAILED', &
377                             __FILE__ , &
378                             __LINE__  )
379    ELSE
380       begin_time = zero_time
381    ENDIF
382 
383    CALL nl_get_history_end_y( grid%id, history_end_y )
384    CALL nl_get_history_end_mo( grid%id, history_end_mo )
385    CALL nl_get_history_end_d( grid%id, history_end_d )
386    CALL nl_get_history_end_h( grid%id, history_end_h )
387    CALL nl_get_history_end_m( grid%id, history_end_m )
388    CALL nl_get_history_end_s( grid%id, history_end_s )
389    IF ( MAX( history_end_y, history_end_mo, history_end_d,   &
390              history_end_h, history_end_m , history_end_s   ) .GT. 0 ) THEN
391       CALL WRFU_TimeIntervalSet( end_time , MM=history_end_mo, D=history_end_d, &
392                                      H=history_end_h, M=history_end_m, S=history_end_s, rc=rc )
393       CALL wrf_check_error( WRFU_SUCCESS, rc, &
394                             'WRFU_TimeIntervalSet(history_end) FAILED', &
395                             __FILE__ , &
396                             __LINE__  )
397    ELSE
398       end_time = run_length + padding_interval
399    ENDIF
400 
401    CALL domain_alarm_create( grid, HISTORY_ALARM, interval, begin_time, end_time )
402 
403    IF ( begin_time .EQ. zero_time ) THEN
404       CALL WRFU_AlarmRingerOn( grid%alarms( HISTORY_ALARM ),  rc=rc )
405       CALL wrf_check_error( WRFU_SUCCESS, rc, &
406                             'WRFU_AlarmRingerOn(HISTORY_ALARM) FAILED', &
407                             __FILE__ , &
408                             __LINE__  )
409    ENDIF
410 
411 
412 ! RESTART INTERVAL
413 ! restart_interval is left there (and means minutes) for consistency, but
414 ! restart_interval_m will take precedence if specified
415    CALL nl_get_restart_interval( 1, restart_interval )   ! same as minutes
416    CALL nl_get_restart_interval_mo( 1, restart_interval_mo )
417    CALL nl_get_restart_interval_d( 1, restart_interval_d )
418    CALL nl_get_restart_interval_h( 1, restart_interval_h )
419    CALL nl_get_restart_interval_m( 1, restart_interval_m )
420    CALL nl_get_restart_interval_s( 1, restart_interval_s )
421    IF ( restart_interval_m .EQ. 0 ) restart_interval_m = restart_interval
422    IF ( MAX( restart_interval_mo, restart_interval_d,   &
423              restart_interval_h, restart_interval_m , restart_interval_s   ) .GT. 0 ) THEN
424      CALL WRFU_TimeIntervalSet( interval, MM=restart_interval_mo, D=restart_interval_d, &
425                                         H=restart_interval_h, M=restart_interval_m, S=restart_interval_s, rc=rc )
426      CALL wrf_check_error( WRFU_SUCCESS, rc, &
427                            'WRFU_TimeIntervalSet(restart_interval) FAILED', &
428                            __FILE__ , &
429                            __LINE__  )
430    ELSE
431      interval = run_length + padding_interval
432    ENDIF
433    CALL domain_alarm_create( grid, RESTART_ALARM, interval )
434 
435 ! INPUTOUT INTERVAL
436    CALL nl_get_inputout_interval( grid%id, inputout_interval )   ! same as minutes
437    CALL nl_get_inputout_interval_mo( grid%id, inputout_interval_mo )
438    CALL nl_get_inputout_interval_d( grid%id, inputout_interval_d )
439    CALL nl_get_inputout_interval_h( grid%id, inputout_interval_h )
440    CALL nl_get_inputout_interval_m( grid%id, inputout_interval_m )
441    CALL nl_get_inputout_interval_s( grid%id, inputout_interval_s )
442    IF ( inputout_interval_m .EQ. 0 ) inputout_interval_m = inputout_interval
443 
444    IF ( MAX( inputout_interval_mo, inputout_interval_d,   &
445              inputout_interval_h, inputout_interval_m , inputout_interval_s   ) .GT. 0 ) THEN
446      CALL WRFU_TimeIntervalSet( interval, MM=inputout_interval_mo, D=inputout_interval_d, &
447                                         H=inputout_interval_h, M=inputout_interval_m, S=inputout_interval_s, rc=rc )
448      CALL wrf_check_error( WRFU_SUCCESS, rc, &
449                            'WRFU_TimeIntervalSet(inputout_interval) FAILED', &
450                            __FILE__ , &
451                            __LINE__  )
452    ELSE
453      interval = run_length + padding_interval
454    ENDIF
455 
456    CALL nl_get_inputout_begin_y( grid%id, inputout_begin_y )
457    CALL nl_get_inputout_begin_mo( grid%id, inputout_begin_mo )
458    CALL nl_get_inputout_begin_d( grid%id, inputout_begin_d )
459    CALL nl_get_inputout_begin_h( grid%id, inputout_begin_h )
460    CALL nl_get_inputout_begin_m( grid%id, inputout_begin_m )
461    CALL nl_get_inputout_begin_s( grid%id, inputout_begin_s )
462    IF ( MAX( inputout_begin_y, inputout_begin_mo, inputout_begin_d,   &
463              inputout_begin_h, inputout_begin_m , inputout_begin_s   ) .GT. 0 ) THEN
464       CALL WRFU_TimeIntervalSet( begin_time , MM=inputout_begin_mo, D=inputout_begin_d, &
465                                       H=inputout_begin_h, M=inputout_begin_m, S=inputout_begin_s, rc=rc )
466       CALL wrf_check_error( WRFU_SUCCESS, rc, &
467                             'WRFU_TimeIntervalSet(inputout_begin) FAILED', &
468                             __FILE__ , &
469                             __LINE__  )
470    ELSE
471       begin_time = zero_time
472    ENDIF
473 
474    CALL nl_get_inputout_end_y( grid%id, inputout_end_y )
475    CALL nl_get_inputout_end_mo( grid%id, inputout_end_mo )
476    CALL nl_get_inputout_end_d( grid%id, inputout_end_d )
477    CALL nl_get_inputout_end_h( grid%id, inputout_end_h )
478    CALL nl_get_inputout_end_m( grid%id, inputout_end_m )
479    CALL nl_get_inputout_end_s( grid%id, inputout_end_s )
480    IF ( MAX( inputout_end_y, inputout_end_mo, inputout_end_d,   &
481              inputout_end_h, inputout_end_m , inputout_end_s   ) .GT. 0 ) THEN
482       CALL WRFU_TimeIntervalSet( end_time , MM=inputout_end_mo, D=inputout_end_d, &
483                                      H=inputout_end_h, M=inputout_end_m, S=inputout_end_s, rc=rc )
484       CALL wrf_check_error( WRFU_SUCCESS, rc, &
485                             'WRFU_TimeIntervalSet(inputout_end) FAILED', &
486                             __FILE__ , &
487                             __LINE__  )
488    ELSE
489       end_time = run_length + padding_interval
490    ENDIF
491 
492    CALL domain_alarm_create( grid, INPUTOUT_ALARM, interval, begin_time, end_time )
493 
494 ! AUXHIST1 INTERVAL
495 ! auxhist1_interval is left there (and means minutes) for consistency, but
496 ! auxhist1_interval_m will take precedence if specified
497    CALL nl_get_auxhist1_interval( grid%id, auxhist1_interval )   ! same as minutes
498    CALL nl_get_auxhist1_interval_mo( grid%id, auxhist1_interval_mo )
499    CALL nl_get_auxhist1_interval_d( grid%id, auxhist1_interval_d )
500    CALL nl_get_auxhist1_interval_h( grid%id, auxhist1_interval_h )
501    CALL nl_get_auxhist1_interval_m( grid%id, auxhist1_interval_m )
502    CALL nl_get_auxhist1_interval_s( grid%id, auxhist1_interval_s )
503    IF ( auxhist1_interval_m .EQ. 0 ) auxhist1_interval_m = auxhist1_interval
504 
505    IF ( MAX( auxhist1_interval_mo, auxhist1_interval_d,   &
506              auxhist1_interval_h, auxhist1_interval_m , auxhist1_interval_s   ) .GT. 0 ) THEN
507      CALL WRFU_TimeIntervalSet( interval, MM=auxhist1_interval_mo, D=auxhist1_interval_d, &
508                                         H=auxhist1_interval_h, M=auxhist1_interval_m, S=auxhist1_interval_s, rc=rc )
509      CALL wrf_check_error( WRFU_SUCCESS, rc, &
510                            'WRFU_TimeIntervalSet(auxhist1_interval) FAILED', &
511                            __FILE__ , &
512                            __LINE__  )
513    ELSE
514      interval = run_length + padding_interval
515    ENDIF
516 
517    CALL nl_get_auxhist1_begin_y( grid%id, auxhist1_begin_y )
518    CALL nl_get_auxhist1_begin_mo( grid%id, auxhist1_begin_mo )
519    CALL nl_get_auxhist1_begin_d( grid%id, auxhist1_begin_d )
520    CALL nl_get_auxhist1_begin_h( grid%id, auxhist1_begin_h )
521    CALL nl_get_auxhist1_begin_m( grid%id, auxhist1_begin_m )
522    CALL nl_get_auxhist1_begin_s( grid%id, auxhist1_begin_s )
523    IF ( MAX( auxhist1_begin_y, auxhist1_begin_mo, auxhist1_begin_d,   &
524              auxhist1_begin_h, auxhist1_begin_m , auxhist1_begin_s   ) .GT. 0 ) THEN
525       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist1_begin_mo, D=auxhist1_begin_d, &
526                                       H=auxhist1_begin_h, M=auxhist1_begin_m, S=auxhist1_begin_s, rc=rc )
527       CALL wrf_check_error( WRFU_SUCCESS, rc, &
528                             'WRFU_TimeIntervalSet(auxhist1_begin) FAILED', &
529                             __FILE__ , &
530                             __LINE__  )
531    ELSE
532       begin_time = zero_time
533    ENDIF
534 
535    CALL nl_get_auxhist1_end_y( grid%id, auxhist1_end_y )
536    CALL nl_get_auxhist1_end_mo( grid%id, auxhist1_end_mo )
537    CALL nl_get_auxhist1_end_d( grid%id, auxhist1_end_d )
538    CALL nl_get_auxhist1_end_h( grid%id, auxhist1_end_h )
539    CALL nl_get_auxhist1_end_m( grid%id, auxhist1_end_m )
540    CALL nl_get_auxhist1_end_s( grid%id, auxhist1_end_s )
541    IF ( MAX( auxhist1_end_y, auxhist1_end_mo, auxhist1_end_d,   &
542              auxhist1_end_h, auxhist1_end_m , auxhist1_end_s   ) .GT. 0 ) THEN
543       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist1_end_mo, D=auxhist1_end_d, &
544                                      H=auxhist1_end_h, M=auxhist1_end_m, S=auxhist1_end_s, rc=rc )
545       CALL wrf_check_error( WRFU_SUCCESS, rc, &
546                             'WRFU_TimeIntervalSet(auxhist1_end) FAILED', &
547                             __FILE__ , &
548                             __LINE__  )
549    ELSE
550       end_time = run_length + padding_interval
551    ENDIF
552 
553    CALL domain_alarm_create( grid, AUXHIST1_ALARM, interval, begin_time, end_time )
554 
555    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
556      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST1_ALARM ),  rc=rc )
557    ENDIF
558 
559 
560 ! AUXHIST2_ INTERVAL
561 ! auxhist2_interval is left there (and means minutes) for consistency, but
562 ! auxhist2_interval_m will take precedence if specified
563    CALL nl_get_auxhist2_interval( grid%id, auxhist2_interval )   ! same as minutes
564    CALL nl_get_auxhist2_interval_mo( grid%id, auxhist2_interval_mo )
565    CALL nl_get_auxhist2_interval_d( grid%id, auxhist2_interval_d )
566    CALL nl_get_auxhist2_interval_h( grid%id, auxhist2_interval_h )
567    CALL nl_get_auxhist2_interval_m( grid%id, auxhist2_interval_m )
568    CALL nl_get_auxhist2_interval_s( grid%id, auxhist2_interval_s )
569    IF ( auxhist2_interval_m .EQ. 0) auxhist2_interval_m = auxhist2_interval
570 
571    IF ( MAX( auxhist2_interval_mo, auxhist2_interval_d,   &
572              auxhist2_interval_h, auxhist2_interval_m , auxhist2_interval_s   ) .GT. 0 ) THEN
573      CALL WRFU_TimeIntervalSet( interval, MM=auxhist2_interval_mo, D=auxhist2_interval_d, &
574                                         H=auxhist2_interval_h, M=auxhist2_interval_m, S=auxhist2_interval_s, rc=rc )
575      CALL wrf_check_error( WRFU_SUCCESS, rc, &
576                            'WRFU_TimeIntervalSet(auxhist2_interval) FAILED', &
577                            __FILE__ , &
578                            __LINE__  )
579    ELSE
580      interval = run_length + padding_interval
581    ENDIF
582 
583    CALL nl_get_auxhist2_begin_y( grid%id, auxhist2_begin_y )
584    CALL nl_get_auxhist2_begin_mo( grid%id, auxhist2_begin_mo )
585    CALL nl_get_auxhist2_begin_d( grid%id, auxhist2_begin_d )
586    CALL nl_get_auxhist2_begin_h( grid%id, auxhist2_begin_h )
587    CALL nl_get_auxhist2_begin_m( grid%id, auxhist2_begin_m )
588    CALL nl_get_auxhist2_begin_s( grid%id, auxhist2_begin_s )
589    IF ( MAX( auxhist2_begin_y, auxhist2_begin_mo, auxhist2_begin_d,   &
590              auxhist2_begin_h, auxhist2_begin_m , auxhist2_begin_s   ) .GT. 0 ) THEN
591       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist2_begin_mo, D=auxhist2_begin_d, &
592                                       H=auxhist2_begin_h, M=auxhist2_begin_m, S=auxhist2_begin_s, rc=rc )
593       CALL wrf_check_error( WRFU_SUCCESS, rc, &
594                             'WRFU_TimeIntervalSet(auxhist2_begin) FAILED', &
595                             __FILE__ , &
596                             __LINE__  )
597    ELSE
598       begin_time = zero_time
599    ENDIF
600 
601    CALL nl_get_auxhist2_end_y( grid%id, auxhist2_end_y )
602    CALL nl_get_auxhist2_end_mo( grid%id, auxhist2_end_mo )
603    CALL nl_get_auxhist2_end_d( grid%id, auxhist2_end_d )
604    CALL nl_get_auxhist2_end_h( grid%id, auxhist2_end_h )
605    CALL nl_get_auxhist2_end_m( grid%id, auxhist2_end_m )
606    CALL nl_get_auxhist2_end_s( grid%id, auxhist2_end_s )
607    IF ( MAX( auxhist2_end_y, auxhist2_end_mo, auxhist2_end_d,   &
608              auxhist2_end_h, auxhist2_end_m , auxhist2_end_s   ) .GT. 0 ) THEN
609       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist2_end_mo, D=auxhist2_end_d, &
610                                      H=auxhist2_end_h, M=auxhist2_end_m, S=auxhist2_end_s, rc=rc )
611       CALL wrf_check_error( WRFU_SUCCESS, rc, &
612                             'WRFU_TimeIntervalSet(auxhist2_end) FAILED', &
613                             __FILE__ , &
614                             __LINE__  )
615    ELSE
616       end_time = run_length + padding_interval
617    ENDIF
618 
619    CALL domain_alarm_create( grid, AUXHIST2_ALARM, interval, begin_time, end_time )
620 
621    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
622      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST2_ALARM ),  rc=rc )
623    ENDIF
624 
625 ! AUXHIST3_ INTERVAL
626 ! auxhist3_interval is left there (and means minutes) for consistency, but
627 ! auxhist3_interval_m will take precedence if specified
628    CALL nl_get_auxhist3_interval( grid%id, auxhist3_interval )   ! same as minutes
629    CALL nl_get_auxhist3_interval_mo( grid%id, auxhist3_interval_mo )
630    CALL nl_get_auxhist3_interval_d( grid%id, auxhist3_interval_d )
631    CALL nl_get_auxhist3_interval_h( grid%id, auxhist3_interval_h )
632    CALL nl_get_auxhist3_interval_m( grid%id, auxhist3_interval_m )
633    CALL nl_get_auxhist3_interval_s( grid%id, auxhist3_interval_s )
634    IF ( auxhist3_interval_m .EQ. 0 ) auxhist3_interval_m = auxhist3_interval
635 
636    IF ( MAX( auxhist3_interval_mo, auxhist3_interval_d,   &
637              auxhist3_interval_h, auxhist3_interval_m , auxhist3_interval_s   ) .GT. 0 ) THEN
638      CALL WRFU_TimeIntervalSet( interval, MM=auxhist3_interval_mo, D=auxhist3_interval_d, &
639                                         H=auxhist3_interval_h, M=auxhist3_interval_m, S=auxhist3_interval_s, rc=rc )
640      CALL wrf_check_error( WRFU_SUCCESS, rc, &
641                            'WRFU_TimeIntervalSet(auxhist3_interval) FAILED', &
642                            __FILE__ , &
643                            __LINE__  )
644    ELSE
645      interval = run_length + padding_interval
646    ENDIF
647 
648    CALL nl_get_auxhist3_begin_y( grid%id, auxhist3_begin_y )
649    CALL nl_get_auxhist3_begin_mo( grid%id, auxhist3_begin_mo )
650    CALL nl_get_auxhist3_begin_d( grid%id, auxhist3_begin_d )
651    CALL nl_get_auxhist3_begin_h( grid%id, auxhist3_begin_h )
652    CALL nl_get_auxhist3_begin_m( grid%id, auxhist3_begin_m )
653    CALL nl_get_auxhist3_begin_s( grid%id, auxhist3_begin_s )
654    IF ( MAX( auxhist3_begin_y, auxhist3_begin_mo, auxhist3_begin_d,   &
655              auxhist3_begin_h, auxhist3_begin_m , auxhist3_begin_s   ) .GT. 0 ) THEN
656       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist3_begin_mo, D=auxhist3_begin_d, &
657                                       H=auxhist3_begin_h, M=auxhist3_begin_m, S=auxhist3_begin_s, rc=rc )
658       CALL wrf_check_error( WRFU_SUCCESS, rc, &
659                             'WRFU_TimeIntervalSet(auxhist3_begin) FAILED', &
660                             __FILE__ , &
661                             __LINE__  )
662    ELSE
663       begin_time = zero_time
664    ENDIF
665 
666    CALL nl_get_auxhist3_end_y( grid%id, auxhist3_end_y )
667    CALL nl_get_auxhist3_end_mo( grid%id, auxhist3_end_mo )
668    CALL nl_get_auxhist3_end_d( grid%id, auxhist3_end_d )
669    CALL nl_get_auxhist3_end_h( grid%id, auxhist3_end_h )
670    CALL nl_get_auxhist3_end_m( grid%id, auxhist3_end_m )
671    CALL nl_get_auxhist3_end_s( grid%id, auxhist3_end_s )
672    IF ( MAX( auxhist3_end_y, auxhist3_end_mo, auxhist3_end_d,   &
673              auxhist3_end_h, auxhist3_end_m , auxhist3_end_s   ) .GT. 0 ) THEN
674       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist3_end_mo, D=auxhist3_end_d, &
675                                      H=auxhist3_end_h, M=auxhist3_end_m, S=auxhist3_end_s, rc=rc )
676       CALL wrf_check_error( WRFU_SUCCESS, rc, &
677                             'WRFU_TimeIntervalSet(auxhist3_end) FAILED', &
678                             __FILE__ , &
679                             __LINE__  )
680    ELSE
681       end_time = run_length + padding_interval
682    ENDIF
683 
684    CALL domain_alarm_create( grid, AUXHIST3_ALARM, interval, begin_time, end_time )
685 
686    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
687      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST3_ALARM ),  rc=rc )
688    ENDIF
689 
690 ! AUXHIST4_ INTERVAL
691 ! auxhist4_interval is left there (and means minutes) for consistency, but
692 ! auxhist4_interval_m will take precedence if specified
693    CALL nl_get_auxhist4_interval( grid%id, auxhist4_interval )   ! same as minutes
694    CALL nl_get_auxhist4_interval_mo( grid%id, auxhist4_interval_mo )
695    CALL nl_get_auxhist4_interval_d( grid%id, auxhist4_interval_d )
696    CALL nl_get_auxhist4_interval_h( grid%id, auxhist4_interval_h )
697    CALL nl_get_auxhist4_interval_m( grid%id, auxhist4_interval_m )
698    CALL nl_get_auxhist4_interval_s( grid%id, auxhist4_interval_s )
699    IF ( auxhist4_interval_m .EQ. 0 ) auxhist4_interval_m = auxhist4_interval
700 
701    IF ( MAX( auxhist4_interval_mo, auxhist4_interval_d,   &
702              auxhist4_interval_h, auxhist4_interval_m , auxhist4_interval_s   ) .GT. 0 ) THEN
703      CALL WRFU_TimeIntervalSet( interval, MM=auxhist4_interval_mo, D=auxhist4_interval_d, &
704                                         H=auxhist4_interval_h, M=auxhist4_interval_m, S=auxhist4_interval_s, rc=rc )
705      CALL wrf_check_error( WRFU_SUCCESS, rc, &
706                            'WRFU_TimeIntervalSet(auxhist4_interval) FAILED', &
707                            __FILE__ , &
708                            __LINE__  )
709    ELSE
710      interval = run_length + padding_interval
711    ENDIF
712 
713    CALL nl_get_auxhist4_begin_y( grid%id, auxhist4_begin_y )
714    CALL nl_get_auxhist4_begin_mo( grid%id, auxhist4_begin_mo )
715    CALL nl_get_auxhist4_begin_d( grid%id, auxhist4_begin_d )
716    CALL nl_get_auxhist4_begin_h( grid%id, auxhist4_begin_h )
717    CALL nl_get_auxhist4_begin_m( grid%id, auxhist4_begin_m )
718    CALL nl_get_auxhist4_begin_s( grid%id, auxhist4_begin_s )
719    IF ( MAX( auxhist4_begin_y, auxhist4_begin_mo, auxhist4_begin_d,   &
720              auxhist4_begin_h, auxhist4_begin_m , auxhist4_begin_s   ) .GT. 0 ) THEN
721       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist4_begin_mo, D=auxhist4_begin_d, &
722                                       H=auxhist4_begin_h, M=auxhist4_begin_m, S=auxhist4_begin_s, rc=rc )
723       CALL wrf_check_error( WRFU_SUCCESS, rc, &
724                             'WRFU_TimeIntervalSet(auxhist4_begin) FAILED', &
725                             __FILE__ , &
726                             __LINE__  )
727    ELSE
728       begin_time = zero_time
729    ENDIF
730 
731    CALL nl_get_auxhist4_end_y( grid%id, auxhist4_end_y )
732    CALL nl_get_auxhist4_end_mo( grid%id, auxhist4_end_mo )
733    CALL nl_get_auxhist4_end_d( grid%id, auxhist4_end_d )
734    CALL nl_get_auxhist4_end_h( grid%id, auxhist4_end_h )
735    CALL nl_get_auxhist4_end_m( grid%id, auxhist4_end_m )
736    CALL nl_get_auxhist4_end_s( grid%id, auxhist4_end_s )
737    IF ( MAX( auxhist4_end_y, auxhist4_end_mo, auxhist4_end_d,   &
738              auxhist4_end_h, auxhist4_end_m , auxhist4_end_s   ) .GT. 0 ) THEN
739       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist4_end_mo, D=auxhist4_end_d, &
740                                      H=auxhist4_end_h, M=auxhist4_end_m, S=auxhist4_end_s, rc=rc )
741       CALL wrf_check_error( WRFU_SUCCESS, rc, &
742                             'WRFU_TimeIntervalSet(auxhist4_end) FAILED', &
743                             __FILE__ , &
744                             __LINE__  )
745    ELSE
746       end_time = run_length + padding_interval
747    ENDIF
748 
749    CALL domain_alarm_create( grid, AUXHIST4_ALARM, interval, begin_time, end_time )
750 
751    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
752      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST4_ALARM ),  rc=rc )
753    ENDIF
754 
755 ! AUXHIST5_ INTERVAL
756 ! auxhist5_interval is left there (and means minutes) for consistency, but
757 ! auxhist5_interval_m will take precedence if specified
758    CALL nl_get_auxhist5_interval( grid%id, auxhist5_interval )   ! same as minutes
759    CALL nl_get_auxhist5_interval_mo( grid%id, auxhist5_interval_mo )
760    CALL nl_get_auxhist5_interval_d( grid%id, auxhist5_interval_d )
761    CALL nl_get_auxhist5_interval_h( grid%id, auxhist5_interval_h )
762    CALL nl_get_auxhist5_interval_m( grid%id, auxhist5_interval_m )
763    CALL nl_get_auxhist5_interval_s( grid%id, auxhist5_interval_s )
764    IF ( auxhist5_interval_m .EQ. 0 ) auxhist5_interval_m = auxhist5_interval
765 
766    IF ( MAX( auxhist5_interval_mo, auxhist5_interval_d,   &
767              auxhist5_interval_h, auxhist5_interval_m , auxhist5_interval_s   ) .GT. 0 ) THEN
768      CALL WRFU_TimeIntervalSet( interval, MM=auxhist5_interval_mo, D=auxhist5_interval_d, &
769                                         H=auxhist5_interval_h, M=auxhist5_interval_m, S=auxhist5_interval_s, rc=rc )
770      CALL wrf_check_error( WRFU_SUCCESS, rc, &
771                            'WRFU_TimeIntervalSet(auxhist5_interval) FAILED', &
772                            __FILE__ , &
773                            __LINE__  )
774    ELSE
775      interval = run_length + padding_interval
776    ENDIF
777 
778    CALL nl_get_auxhist5_begin_y( grid%id, auxhist5_begin_y )
779    CALL nl_get_auxhist5_begin_mo( grid%id, auxhist5_begin_mo )
780    CALL nl_get_auxhist5_begin_d( grid%id, auxhist5_begin_d )
781    CALL nl_get_auxhist5_begin_h( grid%id, auxhist5_begin_h )
782    CALL nl_get_auxhist5_begin_m( grid%id, auxhist5_begin_m )
783    CALL nl_get_auxhist5_begin_s( grid%id, auxhist5_begin_s )
784    IF ( MAX( auxhist5_begin_y, auxhist5_begin_mo, auxhist5_begin_d,   &
785              auxhist5_begin_h, auxhist5_begin_m , auxhist5_begin_s   ) .GT. 0 ) THEN
786       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist5_begin_mo, D=auxhist5_begin_d, &
787                                       H=auxhist5_begin_h, M=auxhist5_begin_m, S=auxhist5_begin_s, rc=rc )
788       CALL wrf_check_error( WRFU_SUCCESS, rc, &
789                             'WRFU_TimeIntervalSet(auxhist5_begin) FAILED', &
790                             __FILE__ , &
791                             __LINE__  )
792    ELSE
793       begin_time = zero_time
794    ENDIF
795 
796    CALL nl_get_auxhist5_end_y( grid%id, auxhist5_end_y )
797    CALL nl_get_auxhist5_end_mo( grid%id, auxhist5_end_mo )
798    CALL nl_get_auxhist5_end_d( grid%id, auxhist5_end_d )
799    CALL nl_get_auxhist5_end_h( grid%id, auxhist5_end_h )
800    CALL nl_get_auxhist5_end_m( grid%id, auxhist5_end_m )
801    CALL nl_get_auxhist5_end_s( grid%id, auxhist5_end_s )
802    IF ( MAX( auxhist5_end_y, auxhist5_end_mo, auxhist5_end_d,   &
803              auxhist5_end_h, auxhist5_end_m , auxhist5_end_s   ) .GT. 0 ) THEN
804       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist5_end_mo, D=auxhist5_end_d, &
805                                      H=auxhist5_end_h, M=auxhist5_end_m, S=auxhist5_end_s, rc=rc )
806       CALL wrf_check_error( WRFU_SUCCESS, rc, &
807                             'WRFU_TimeIntervalSet(auxhist5_end) FAILED', &
808                             __FILE__ , &
809                             __LINE__  )
810    ELSE
811       end_time = run_length + padding_interval
812    ENDIF
813 
814    CALL domain_alarm_create( grid, AUXHIST5_ALARM, interval, begin_time, end_time )
815 
816    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
817      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST5_ALARM ),  rc=rc )
818    ENDIF
819 
820 ! AUXHIST6_ INTERVAL
821 ! auxhist6_interval is left there (and means minutes) for consistency, but
822 ! auxhist6_interval_m will take precedence if specified
823    CALL nl_get_auxhist6_interval( grid%id, auxhist6_interval )   ! same as minutes
824    CALL nl_get_auxhist6_interval_mo( grid%id, auxhist6_interval_mo )
825    CALL nl_get_auxhist6_interval_d( grid%id, auxhist6_interval_d )
826    CALL nl_get_auxhist6_interval_h( grid%id, auxhist6_interval_h )
827    CALL nl_get_auxhist6_interval_m( grid%id, auxhist6_interval_m )
828    CALL nl_get_auxhist6_interval_s( grid%id, auxhist6_interval_s )
829    IF ( auxhist6_interval_m .EQ. 0 ) auxhist6_interval_m = auxhist6_interval
830 
831    IF ( MAX( auxhist6_interval_mo, auxhist6_interval_d,   &
832              auxhist6_interval_h, auxhist6_interval_m , auxhist6_interval_s   ) .GT. 0 ) THEN
833      CALL WRFU_TimeIntervalSet( interval, MM=auxhist6_interval_mo, D=auxhist6_interval_d, &
834                                         H=auxhist6_interval_h, M=auxhist6_interval_m, S=auxhist6_interval_s, rc=rc )
835      CALL wrf_check_error( WRFU_SUCCESS, rc, &
836                            'WRFU_TimeIntervalSet(auxhist6_interval) FAILED', &
837                            __FILE__ , &
838                            __LINE__  )
839    ELSE
840      interval = run_length + padding_interval
841    ENDIF
842 
843    CALL nl_get_auxhist6_begin_y( grid%id, auxhist6_begin_y )
844    CALL nl_get_auxhist6_begin_mo( grid%id, auxhist6_begin_mo )
845    CALL nl_get_auxhist6_begin_d( grid%id, auxhist6_begin_d )
846    CALL nl_get_auxhist6_begin_h( grid%id, auxhist6_begin_h )
847    CALL nl_get_auxhist6_begin_m( grid%id, auxhist6_begin_m )
848    CALL nl_get_auxhist6_begin_s( grid%id, auxhist6_begin_s )
849    IF ( MAX( auxhist6_begin_y, auxhist6_begin_mo, auxhist6_begin_d,   &
850              auxhist6_begin_h, auxhist6_begin_m , auxhist6_begin_s   ) .GT. 0 ) THEN
851       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist6_begin_mo, D=auxhist6_begin_d, &
852                                       H=auxhist6_begin_h, M=auxhist6_begin_m, S=auxhist6_begin_s, rc=rc )
853       CALL wrf_check_error( WRFU_SUCCESS, rc, &
854                             'WRFU_TimeIntervalSet(auxhist6_begin) FAILED', &
855                             __FILE__ , &
856                             __LINE__  )
857    ELSE
858       begin_time = zero_time
859    ENDIF
860 
861    CALL nl_get_auxhist6_end_y( grid%id, auxhist6_end_y )
862    CALL nl_get_auxhist6_end_mo( grid%id, auxhist6_end_mo )
863    CALL nl_get_auxhist6_end_d( grid%id, auxhist6_end_d )
864    CALL nl_get_auxhist6_end_h( grid%id, auxhist6_end_h )
865    CALL nl_get_auxhist6_end_m( grid%id, auxhist6_end_m )
866    CALL nl_get_auxhist6_end_s( grid%id, auxhist6_end_s )
867    IF ( MAX( auxhist6_end_y, auxhist6_end_mo, auxhist6_end_d,   &
868              auxhist6_end_h, auxhist6_end_m , auxhist6_end_s   ) .GT. 0 ) THEN
869       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist6_end_mo, D=auxhist6_end_d, &
870                                      H=auxhist6_end_h, M=auxhist6_end_m, S=auxhist6_end_s, rc=rc )
871       CALL wrf_check_error( WRFU_SUCCESS, rc, &
872                             'WRFU_TimeIntervalSet(auxhist6_end) FAILED', &
873                             __FILE__ , &
874                             __LINE__  )
875    ELSE
876       end_time = run_length + padding_interval
877    ENDIF
878 
879    CALL domain_alarm_create( grid, AUXHIST6_ALARM, interval, begin_time, end_time )
880 
881    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
882      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST6_ALARM ),  rc=rc )
883    ENDIF
884 
885 
886 ! AUXHIST7_ INTERVAL
887 ! auxhist7_interval is left there (and means minutes) for consistency, but
888 ! auxhist7_interval_m will take precedence if specified
889    CALL nl_get_auxhist7_interval( grid%id, auxhist7_interval )   ! same as minutes
890    CALL nl_get_auxhist7_interval_mo( grid%id, auxhist7_interval_mo )
891    CALL nl_get_auxhist7_interval_d( grid%id, auxhist7_interval_d )
892    CALL nl_get_auxhist7_interval_h( grid%id, auxhist7_interval_h )
893    CALL nl_get_auxhist7_interval_m( grid%id, auxhist7_interval_m )
894    CALL nl_get_auxhist7_interval_s( grid%id, auxhist7_interval_s )
895    IF ( auxhist7_interval_m .EQ. 0 ) auxhist7_interval_m = auxhist7_interval
896 
897    IF ( MAX( auxhist7_interval_mo, auxhist7_interval_d,   &
898              auxhist7_interval_h, auxhist7_interval_m , auxhist7_interval_s   ) .GT. 0 ) THEN
899      CALL WRFU_TimeIntervalSet( interval, MM=auxhist7_interval_mo, D=auxhist7_interval_d, &
900                                         H=auxhist7_interval_h, M=auxhist7_interval_m, S=auxhist7_interval_s, rc=rc )
901      CALL wrf_check_error( WRFU_SUCCESS, rc, &
902                            'WRFU_TimeIntervalSet(auxhist7_interval) FAILED', &
903                            __FILE__ , &
904                            __LINE__  )
905    ELSE
906      interval = run_length + padding_interval
907    ENDIF
908 
909    CALL nl_get_auxhist7_begin_y( grid%id, auxhist7_begin_y )
910    CALL nl_get_auxhist7_begin_mo( grid%id, auxhist7_begin_mo )
911    CALL nl_get_auxhist7_begin_d( grid%id, auxhist7_begin_d )
912    CALL nl_get_auxhist7_begin_h( grid%id, auxhist7_begin_h )
913    CALL nl_get_auxhist7_begin_m( grid%id, auxhist7_begin_m )
914    CALL nl_get_auxhist7_begin_s( grid%id, auxhist7_begin_s )
915    IF ( MAX( auxhist7_begin_y, auxhist7_begin_mo, auxhist7_begin_d,   &
916              auxhist7_begin_h, auxhist7_begin_m , auxhist7_begin_s   ) .GT. 0 ) THEN
917       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist7_begin_mo, D=auxhist7_begin_d, &
918                                       H=auxhist7_begin_h, M=auxhist7_begin_m, S=auxhist7_begin_s, rc=rc )
919       CALL wrf_check_error( WRFU_SUCCESS, rc, &
920                             'WRFU_TimeIntervalSet(auxhist7_begin) FAILED', &
921                             __FILE__ , &
922                             __LINE__  )
923    ELSE
924       begin_time = zero_time
925    ENDIF
926 
927    CALL nl_get_auxhist7_end_y( grid%id, auxhist7_end_y )
928    CALL nl_get_auxhist7_end_mo( grid%id, auxhist7_end_mo )
929    CALL nl_get_auxhist7_end_d( grid%id, auxhist7_end_d )
930    CALL nl_get_auxhist7_end_h( grid%id, auxhist7_end_h )
931    CALL nl_get_auxhist7_end_m( grid%id, auxhist7_end_m )
932    CALL nl_get_auxhist7_end_s( grid%id, auxhist7_end_s )
933    IF ( MAX( auxhist7_end_y, auxhist7_end_mo, auxhist7_end_d,   &
934              auxhist7_end_h, auxhist7_end_m , auxhist7_end_s   ) .GT. 0 ) THEN
935       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist7_end_mo, D=auxhist7_end_d, &
936                                      H=auxhist7_end_h, M=auxhist7_end_m, S=auxhist7_end_s, rc=rc )
937       CALL wrf_check_error( WRFU_SUCCESS, rc, &
938                             'WRFU_TimeIntervalSet(auxhist7_end) FAILED', &
939                             __FILE__ , &
940                             __LINE__  )
941    ELSE
942       end_time = run_length + padding_interval
943    ENDIF
944 
945    CALL domain_alarm_create( grid, AUXHIST7_ALARM, interval, begin_time, end_time )
946 
947    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
948      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST7_ALARM ),  rc=rc )
949    ENDIF
950 
951 ! AUXHIST8_ INTERVAL
952 ! auxhist8_interval is left there (and means minutes) for consistency, but
953 ! auxhist8_interval_m will take precedence if specified
954    CALL nl_get_auxhist8_interval( grid%id, auxhist8_interval )   ! same as minutes
955    CALL nl_get_auxhist8_interval_mo( grid%id, auxhist8_interval_mo )
956    CALL nl_get_auxhist8_interval_d( grid%id, auxhist8_interval_d )
957    CALL nl_get_auxhist8_interval_h( grid%id, auxhist8_interval_h )
958    CALL nl_get_auxhist8_interval_m( grid%id, auxhist8_interval_m )
959    CALL nl_get_auxhist8_interval_s( grid%id, auxhist8_interval_s )
960    IF ( auxhist8_interval_m .EQ. 0 ) auxhist8_interval_m = auxhist8_interval
961 
962    IF ( MAX( auxhist8_interval_mo, auxhist8_interval_d,   &
963              auxhist8_interval_h, auxhist8_interval_m , auxhist8_interval_s   ) .GT. 0 ) THEN
964      CALL WRFU_TimeIntervalSet( interval, MM=auxhist8_interval_mo, D=auxhist8_interval_d, &
965                                         H=auxhist8_interval_h, M=auxhist8_interval_m, S=auxhist8_interval_s, rc=rc )
966      CALL wrf_check_error( WRFU_SUCCESS, rc, &
967                            'WRFU_TimeIntervalSet(auxhist8_interval) FAILED', &
968                            __FILE__ , &
969                            __LINE__  )
970    ELSE
971      interval = run_length + padding_interval
972    ENDIF
973 
974    CALL nl_get_auxhist8_begin_y( grid%id, auxhist8_begin_y )
975    CALL nl_get_auxhist8_begin_mo( grid%id, auxhist8_begin_mo )
976    CALL nl_get_auxhist8_begin_d( grid%id, auxhist8_begin_d )
977    CALL nl_get_auxhist8_begin_h( grid%id, auxhist8_begin_h )
978    CALL nl_get_auxhist8_begin_m( grid%id, auxhist8_begin_m )
979    CALL nl_get_auxhist8_begin_s( grid%id, auxhist8_begin_s )
980    IF ( MAX( auxhist8_begin_y, auxhist8_begin_mo, auxhist8_begin_d,   &
981              auxhist8_begin_h, auxhist8_begin_m , auxhist8_begin_s   ) .GT. 0 ) THEN
982       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist8_begin_mo, D=auxhist8_begin_d, &
983                                       H=auxhist8_begin_h, M=auxhist8_begin_m, S=auxhist8_begin_s, rc=rc )
984       CALL wrf_check_error( WRFU_SUCCESS, rc, &
985                             'WRFU_TimeIntervalSet(auxhist8_begin) FAILED', &
986                             __FILE__ , &
987                             __LINE__  )
988    ELSE
989       begin_time = zero_time
990    ENDIF
991 
992    CALL nl_get_auxhist8_end_y( grid%id, auxhist8_end_y )
993    CALL nl_get_auxhist8_end_mo( grid%id, auxhist8_end_mo )
994    CALL nl_get_auxhist8_end_d( grid%id, auxhist8_end_d )
995    CALL nl_get_auxhist8_end_h( grid%id, auxhist8_end_h )
996    CALL nl_get_auxhist8_end_m( grid%id, auxhist8_end_m )
997    CALL nl_get_auxhist8_end_s( grid%id, auxhist8_end_s )
998    IF ( MAX( auxhist8_end_y, auxhist8_end_mo, auxhist8_end_d,   &
999              auxhist8_end_h, auxhist8_end_m , auxhist8_end_s   ) .GT. 0 ) THEN
1000       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist8_end_mo, D=auxhist8_end_d, &
1001                                      H=auxhist8_end_h, M=auxhist8_end_m, S=auxhist8_end_s, rc=rc )
1002       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1003                             'WRFU_TimeIntervalSet(auxhist8_end) FAILED', &
1004                             __FILE__ , &
1005                             __LINE__  )
1006    ELSE
1007       end_time = run_length + padding_interval
1008    ENDIF
1009 
1010    CALL domain_alarm_create( grid, AUXHIST8_ALARM, interval, begin_time, end_time )
1011 
1012    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1013      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST8_ALARM ),  rc=rc )
1014    ENDIF
1015 
1016 ! AUXHIST9_ INTERVAL
1017 ! auxhist9_interval is left there (and means minutes) for consistency, but
1018 ! auxhist9_interval_m will take precedence if specified
1019    CALL nl_get_auxhist9_interval( grid%id, auxhist9_interval )   ! same as minutes
1020    CALL nl_get_auxhist9_interval_mo( grid%id, auxhist9_interval_mo )
1021    CALL nl_get_auxhist9_interval_d( grid%id, auxhist9_interval_d )
1022    CALL nl_get_auxhist9_interval_h( grid%id, auxhist9_interval_h )
1023    CALL nl_get_auxhist9_interval_m( grid%id, auxhist9_interval_m )
1024    CALL nl_get_auxhist9_interval_s( grid%id, auxhist9_interval_s )
1025    IF ( auxhist9_interval_m .EQ. 0 ) auxhist9_interval_m = auxhist9_interval
1026 
1027    IF ( MAX( auxhist9_interval_mo, auxhist9_interval_d,   &
1028              auxhist9_interval_h, auxhist9_interval_m , auxhist9_interval_s   ) .GT. 0 ) THEN
1029      CALL WRFU_TimeIntervalSet( interval, MM=auxhist9_interval_mo, D=auxhist9_interval_d, &
1030                                         H=auxhist9_interval_h, M=auxhist9_interval_m, S=auxhist9_interval_s, rc=rc )
1031      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1032                            'WRFU_TimeIntervalSet(auxhist9_interval) FAILED', &
1033                            __FILE__ , &
1034                            __LINE__  )
1035    ELSE
1036      interval = run_length + padding_interval
1037    ENDIF
1038 
1039    CALL nl_get_auxhist9_begin_y( grid%id, auxhist9_begin_y )
1040    CALL nl_get_auxhist9_begin_mo( grid%id, auxhist9_begin_mo )
1041    CALL nl_get_auxhist9_begin_d( grid%id, auxhist9_begin_d )
1042    CALL nl_get_auxhist9_begin_h( grid%id, auxhist9_begin_h )
1043    CALL nl_get_auxhist9_begin_m( grid%id, auxhist9_begin_m )
1044    CALL nl_get_auxhist9_begin_s( grid%id, auxhist9_begin_s )
1045    IF ( MAX( auxhist9_begin_y, auxhist9_begin_mo, auxhist9_begin_d,   &
1046              auxhist9_begin_h, auxhist9_begin_m , auxhist9_begin_s   ) .GT. 0 ) THEN
1047       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist9_begin_mo, D=auxhist9_begin_d, &
1048                                       H=auxhist9_begin_h, M=auxhist9_begin_m, S=auxhist9_begin_s, rc=rc )
1049       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1050                             'WRFU_TimeIntervalSet(auxhist9_begin) FAILED', &
1051                             __FILE__ , &
1052                             __LINE__  )
1053    ELSE
1054       begin_time = zero_time
1055    ENDIF
1056 
1057    CALL nl_get_auxhist9_end_y( grid%id, auxhist9_end_y )
1058    CALL nl_get_auxhist9_end_mo( grid%id, auxhist9_end_mo )
1059    CALL nl_get_auxhist9_end_d( grid%id, auxhist9_end_d )
1060    CALL nl_get_auxhist9_end_h( grid%id, auxhist9_end_h )
1061    CALL nl_get_auxhist9_end_m( grid%id, auxhist9_end_m )
1062    CALL nl_get_auxhist9_end_s( grid%id, auxhist9_end_s )
1063    IF ( MAX( auxhist9_end_y, auxhist9_end_mo, auxhist9_end_d,   &
1064              auxhist9_end_h, auxhist9_end_m , auxhist9_end_s   ) .GT. 0 ) THEN
1065       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist9_end_mo, D=auxhist9_end_d, &
1066                                      H=auxhist9_end_h, M=auxhist9_end_m, S=auxhist9_end_s, rc=rc )
1067       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1068                             'WRFU_TimeIntervalSet(auxhist9_end) FAILED', &
1069                             __FILE__ , &
1070                             __LINE__  )
1071    ELSE
1072       end_time = run_length + padding_interval
1073    ENDIF
1074 
1075    CALL domain_alarm_create( grid, AUXHIST9_ALARM, interval, begin_time, end_time )
1076 
1077    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1078      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST9_ALARM ),  rc=rc )
1079    ENDIF
1080 
1081 ! AUXHIST10_ INTERVAL
1082 ! auxhist10_interval is left there (and means minutes) for consistency, but
1083 ! auxhist10_interval_m will take precedence if specified
1084    CALL nl_get_auxhist10_interval( grid%id, auxhist10_interval )   ! same as minutes
1085    CALL nl_get_auxhist10_interval_mo( grid%id, auxhist10_interval_mo )
1086    CALL nl_get_auxhist10_interval_d( grid%id, auxhist10_interval_d )
1087    CALL nl_get_auxhist10_interval_h( grid%id, auxhist10_interval_h )
1088    CALL nl_get_auxhist10_interval_m( grid%id, auxhist10_interval_m )
1089    CALL nl_get_auxhist10_interval_s( grid%id, auxhist10_interval_s )
1090    IF ( auxhist10_interval_m .EQ. 0 ) auxhist10_interval_m = auxhist10_interval
1091 
1092    IF ( MAX( auxhist10_interval_mo, auxhist10_interval_d,   &
1093              auxhist10_interval_h, auxhist10_interval_m , auxhist10_interval_s   ) .GT. 0 ) THEN
1094      CALL WRFU_TimeIntervalSet( interval, MM=auxhist10_interval_mo, D=auxhist10_interval_d, &
1095                                         H=auxhist10_interval_h, M=auxhist10_interval_m, S=auxhist10_interval_s, rc=rc )
1096      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1097                            'WRFU_TimeIntervalSet(auxhist10_interval) FAILED', &
1098                            __FILE__ , &
1099                            __LINE__  )
1100    ELSE
1101      interval = run_length + padding_interval
1102    ENDIF
1103 
1104    CALL nl_get_auxhist10_begin_y( grid%id, auxhist10_begin_y )
1105    CALL nl_get_auxhist10_begin_mo( grid%id, auxhist10_begin_mo )
1106    CALL nl_get_auxhist10_begin_d( grid%id, auxhist10_begin_d )
1107    CALL nl_get_auxhist10_begin_h( grid%id, auxhist10_begin_h )
1108    CALL nl_get_auxhist10_begin_m( grid%id, auxhist10_begin_m )
1109    CALL nl_get_auxhist10_begin_s( grid%id, auxhist10_begin_s )
1110    IF ( MAX( auxhist10_begin_y, auxhist10_begin_mo, auxhist10_begin_d,   &
1111              auxhist10_begin_h, auxhist10_begin_m , auxhist10_begin_s   ) .GT. 0 ) THEN
1112       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist10_begin_mo, D=auxhist10_begin_d, &
1113                                       H=auxhist10_begin_h, M=auxhist10_begin_m, S=auxhist10_begin_s, rc=rc )
1114       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1115                             'WRFU_TimeIntervalSet(auxhist10_begin) FAILED', &
1116                             __FILE__ , &
1117                             __LINE__  )
1118    ELSE
1119       begin_time = zero_time
1120    ENDIF
1121 
1122    CALL nl_get_auxhist10_end_y( grid%id, auxhist10_end_y )
1123    CALL nl_get_auxhist10_end_mo( grid%id, auxhist10_end_mo )
1124    CALL nl_get_auxhist10_end_d( grid%id, auxhist10_end_d )
1125    CALL nl_get_auxhist10_end_h( grid%id, auxhist10_end_h )
1126    CALL nl_get_auxhist10_end_m( grid%id, auxhist10_end_m )
1127    CALL nl_get_auxhist10_end_s( grid%id, auxhist10_end_s )
1128    IF ( MAX( auxhist10_end_y, auxhist10_end_mo, auxhist10_end_d,   &
1129              auxhist10_end_h, auxhist10_end_m , auxhist10_end_s   ) .GT. 0 ) THEN
1130       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist10_end_mo, D=auxhist10_end_d, &
1131                                      H=auxhist10_end_h, M=auxhist10_end_m, S=auxhist10_end_s, rc=rc )
1132       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1133                             'WRFU_TimeIntervalSet(auxhist10_end) FAILED', &
1134                             __FILE__ , &
1135                             __LINE__  )
1136    ELSE
1137       end_time = run_length + padding_interval
1138    ENDIF
1139 
1140    CALL domain_alarm_create( grid, AUXHIST10_ALARM, interval, begin_time, end_time )
1141 
1142    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1143      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST10_ALARM ),  rc=rc )
1144    ENDIF
1145 
1146 ! AUXHIST11_ INTERVAL
1147 ! auxhist11_interval is left there (and means minutes) for consistency, but
1148 ! auxhist11_interval_m will take precedence if specified
1149    CALL nl_get_auxhist11_interval( grid%id, auxhist11_interval )   ! same as minutes
1150    CALL nl_get_auxhist11_interval_mo( grid%id, auxhist11_interval_mo )
1151    CALL nl_get_auxhist11_interval_d( grid%id, auxhist11_interval_d )
1152    CALL nl_get_auxhist11_interval_h( grid%id, auxhist11_interval_h )
1153    CALL nl_get_auxhist11_interval_m( grid%id, auxhist11_interval_m )
1154    CALL nl_get_auxhist11_interval_s( grid%id, auxhist11_interval_s )
1155    IF ( auxhist11_interval_m .EQ. 0 ) auxhist11_interval_m = auxhist11_interval
1156 
1157    IF ( MAX( auxhist11_interval_mo, auxhist11_interval_d,   &
1158              auxhist11_interval_h, auxhist11_interval_m , auxhist11_interval_s   ) .GT. 0 ) THEN
1159      CALL WRFU_TimeIntervalSet( interval, MM=auxhist11_interval_mo, D=auxhist11_interval_d, &
1160                                         H=auxhist11_interval_h, M=auxhist11_interval_m, S=auxhist11_interval_s, rc=rc )
1161      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1162                            'WRFU_TimeIntervalSet(auxhist11_interval) FAILED', &
1163                            __FILE__ , &
1164                            __LINE__  )
1165    ELSE
1166      interval = run_length + padding_interval
1167    ENDIF
1168 
1169    CALL nl_get_auxhist11_begin_y( grid%id, auxhist11_begin_y )
1170    CALL nl_get_auxhist11_begin_mo( grid%id, auxhist11_begin_mo )
1171    CALL nl_get_auxhist11_begin_d( grid%id, auxhist11_begin_d )
1172    CALL nl_get_auxhist11_begin_h( grid%id, auxhist11_begin_h )
1173    CALL nl_get_auxhist11_begin_m( grid%id, auxhist11_begin_m )
1174    CALL nl_get_auxhist11_begin_s( grid%id, auxhist11_begin_s )
1175    IF ( MAX( auxhist11_begin_y, auxhist11_begin_mo, auxhist11_begin_d,   &
1176              auxhist11_begin_h, auxhist11_begin_m , auxhist11_begin_s   ) .GT. 0 ) THEN
1177       CALL WRFU_TimeIntervalSet( begin_time , MM=auxhist11_begin_mo, D=auxhist11_begin_d, &
1178                                       H=auxhist11_begin_h, M=auxhist11_begin_m, S=auxhist11_begin_s, rc=rc )
1179       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1180                             'WRFU_TimeIntervalSet(auxhist11_begin) FAILED', &
1181                             __FILE__ , &
1182                             __LINE__  )
1183    ELSE
1184       begin_time = zero_time
1185    ENDIF
1186 
1187    CALL nl_get_auxhist11_end_y( grid%id, auxhist11_end_y )
1188    CALL nl_get_auxhist11_end_mo( grid%id, auxhist11_end_mo )
1189    CALL nl_get_auxhist11_end_d( grid%id, auxhist11_end_d )
1190    CALL nl_get_auxhist11_end_h( grid%id, auxhist11_end_h )
1191    CALL nl_get_auxhist11_end_m( grid%id, auxhist11_end_m )
1192    CALL nl_get_auxhist11_end_s( grid%id, auxhist11_end_s )
1193    IF ( MAX( auxhist11_end_y, auxhist11_end_mo, auxhist11_end_d,   &
1194              auxhist11_end_h, auxhist11_end_m , auxhist11_end_s   ) .GT. 0 ) THEN
1195       CALL WRFU_TimeIntervalSet( end_time , MM=auxhist11_end_mo, D=auxhist11_end_d, &
1196                                      H=auxhist11_end_h, M=auxhist11_end_m, S=auxhist11_end_s, rc=rc )
1197       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1198                             'WRFU_TimeIntervalSet(auxhist11_end) FAILED', &
1199                             __FILE__ , &
1200                             __LINE__  )
1201    ELSE
1202       end_time = run_length + padding_interval
1203    ENDIF
1204 
1205    CALL domain_alarm_create( grid, AUXHIST11_ALARM, interval, begin_time, end_time )
1206 
1207    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1208      CALL WRFU_AlarmRingerOn( grid%alarms( AUXHIST11_ALARM ),  rc=rc )
1209    ENDIF
1210 
1211 ! AUXINPUT1_ INTERVAL
1212 ! auxinput1_interval is left there (and means minutes) for consistency, but
1213 ! auxinput1_interval_m will take precedence if specified
1214    CALL nl_get_auxinput1_interval( grid%id, auxinput1_interval )   ! same as minutes
1215    CALL nl_get_auxinput1_interval_mo( grid%id, auxinput1_interval_mo )
1216    CALL nl_get_auxinput1_interval_d( grid%id, auxinput1_interval_d )
1217    CALL nl_get_auxinput1_interval_h( grid%id, auxinput1_interval_h )
1218    CALL nl_get_auxinput1_interval_m( grid%id, auxinput1_interval_m )
1219    CALL nl_get_auxinput1_interval_s( grid%id, auxinput1_interval_s )
1220    IF ( auxinput1_interval_m .EQ. 0 ) auxinput1_interval_m = auxinput1_interval
1221 
1222    IF ( MAX( auxinput1_interval_mo, auxinput1_interval_d,   &
1223              auxinput1_interval_h, auxinput1_interval_m , auxinput1_interval_s   ) .GT. 0 ) THEN
1224      CALL WRFU_TimeIntervalSet( interval, MM=auxinput1_interval_mo, D=auxinput1_interval_d, &
1225                                         H=auxinput1_interval_h, M=auxinput1_interval_m, S=auxinput1_interval_s, rc=rc )
1226      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1227                            'WRFU_TimeIntervalSet(auxinput1_interval) FAILED', &
1228                            __FILE__ , &
1229                            __LINE__  )
1230    ELSE
1231      interval = run_length + padding_interval
1232    ENDIF
1233 
1234    CALL nl_get_auxinput1_begin_y( grid%id, auxinput1_begin_y )
1235    CALL nl_get_auxinput1_begin_mo( grid%id, auxinput1_begin_mo )
1236    CALL nl_get_auxinput1_begin_d( grid%id, auxinput1_begin_d )
1237    CALL nl_get_auxinput1_begin_h( grid%id, auxinput1_begin_h )
1238    CALL nl_get_auxinput1_begin_m( grid%id, auxinput1_begin_m )
1239    CALL nl_get_auxinput1_begin_s( grid%id, auxinput1_begin_s )
1240    IF ( MAX( auxinput1_begin_y, auxinput1_begin_mo, auxinput1_begin_d,   &
1241              auxinput1_begin_h, auxinput1_begin_m , auxinput1_begin_s   ) .GT. 0 ) THEN
1242       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput1_begin_mo, D=auxinput1_begin_d, &
1243                                       H=auxinput1_begin_h, M=auxinput1_begin_m, S=auxinput1_begin_s, rc=rc )
1244       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1245                             'WRFU_TimeIntervalSet(auxinput1_begin) FAILED', &
1246                             __FILE__ , &
1247                             __LINE__  )
1248    ELSE
1249       begin_time = zero_time
1250    ENDIF
1251 
1252    CALL nl_get_auxinput1_end_y( grid%id, auxinput1_end_y )
1253    CALL nl_get_auxinput1_end_mo( grid%id, auxinput1_end_mo )
1254    CALL nl_get_auxinput1_end_d( grid%id, auxinput1_end_d )
1255    CALL nl_get_auxinput1_end_h( grid%id, auxinput1_end_h )
1256    CALL nl_get_auxinput1_end_m( grid%id, auxinput1_end_m )
1257    CALL nl_get_auxinput1_end_s( grid%id, auxinput1_end_s )
1258    IF ( MAX( auxinput1_end_y, auxinput1_end_mo, auxinput1_end_d,   &
1259              auxinput1_end_h, auxinput1_end_m , auxinput1_end_s   ) .GT. 0 ) THEN
1260       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput1_end_mo, D=auxinput1_end_d, &
1261                                      H=auxinput1_end_h, M=auxinput1_end_m, S=auxinput1_end_s, rc=rc )
1262       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1263                             'WRFU_TimeIntervalSet(auxinput1_end) FAILED', &
1264                             __FILE__ , &
1265                             __LINE__  )
1266    ELSE
1267       end_time = run_length + padding_interval
1268    ENDIF
1269 
1270    CALL domain_alarm_create( grid, AUXINPUT1_ALARM, interval, begin_time, end_time )
1271 
1272    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1273      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT1_ALARM ),  rc=rc )
1274      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1275                            'WRFU_AlarmRingerOn(AUXINPUT1_ALARM) FAILED', &
1276                            __FILE__ , &
1277                            __LINE__  )
1278    ENDIF
1279 
1280 ! AUXINPUT2_ INTERVAL
1281 ! auxinput2_interval is left there (and means minutes) for consistency, but
1282 ! auxinput2_interval_m will take precedence if specified
1283    CALL nl_get_auxinput2_interval( grid%id, auxinput2_interval )   ! same as minutes
1284    CALL nl_get_auxinput2_interval_mo( grid%id, auxinput2_interval_mo )
1285    CALL nl_get_auxinput2_interval_d( grid%id, auxinput2_interval_d )
1286    CALL nl_get_auxinput2_interval_h( grid%id, auxinput2_interval_h )
1287    CALL nl_get_auxinput2_interval_m( grid%id, auxinput2_interval_m )
1288    CALL nl_get_auxinput2_interval_s( grid%id, auxinput2_interval_s )
1289    IF ( auxinput2_interval_m .EQ. 0 ) auxinput2_interval_m = auxinput2_interval
1290 
1291    IF ( MAX( auxinput2_interval_mo, auxinput2_interval_d,   &
1292              auxinput2_interval_h, auxinput2_interval_m , auxinput2_interval_s   ) .GT. 0 ) THEN
1293      CALL WRFU_TimeIntervalSet( interval, MM=auxinput2_interval_mo, D=auxinput2_interval_d, &
1294                                         H=auxinput2_interval_h, M=auxinput2_interval_m, S=auxinput2_interval_s, rc=rc )
1295      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1296                            'WRFU_TimeIntervalSet(auxinput2_interval) FAILED', &
1297                            __FILE__ , &
1298                            __LINE__  )
1299    ELSE
1300      interval = run_length + padding_interval
1301    ENDIF
1302 
1303    CALL nl_get_auxinput2_begin_y( grid%id, auxinput2_begin_y )
1304    CALL nl_get_auxinput2_begin_mo( grid%id, auxinput2_begin_mo )
1305    CALL nl_get_auxinput2_begin_d( grid%id, auxinput2_begin_d )
1306    CALL nl_get_auxinput2_begin_h( grid%id, auxinput2_begin_h )
1307    CALL nl_get_auxinput2_begin_m( grid%id, auxinput2_begin_m )
1308    CALL nl_get_auxinput2_begin_s( grid%id, auxinput2_begin_s )
1309    IF ( MAX( auxinput2_begin_y, auxinput2_begin_mo, auxinput2_begin_d,   &
1310              auxinput2_begin_h, auxinput2_begin_m , auxinput2_begin_s   ) .GT. 0 ) THEN
1311       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput2_begin_mo, D=auxinput2_begin_d, &
1312                                       H=auxinput2_begin_h, M=auxinput2_begin_m, S=auxinput2_begin_s, rc=rc )
1313       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1314                             'WRFU_TimeIntervalSet(auxinput2_begin) FAILED', &
1315                             __FILE__ , &
1316                             __LINE__  )
1317    ELSE
1318       begin_time = zero_time
1319    ENDIF
1320 
1321    CALL nl_get_auxinput2_end_y( grid%id, auxinput2_end_y )
1322    CALL nl_get_auxinput2_end_mo( grid%id, auxinput2_end_mo )
1323    CALL nl_get_auxinput2_end_d( grid%id, auxinput2_end_d )
1324    CALL nl_get_auxinput2_end_h( grid%id, auxinput2_end_h )
1325    CALL nl_get_auxinput2_end_m( grid%id, auxinput2_end_m )
1326    CALL nl_get_auxinput2_end_s( grid%id, auxinput2_end_s )
1327    IF ( MAX( auxinput2_end_y, auxinput2_end_mo, auxinput2_end_d,   &
1328              auxinput2_end_h, auxinput2_end_m , auxinput2_end_s   ) .GT. 0 ) THEN
1329       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput2_end_mo, D=auxinput2_end_d, &
1330                                      H=auxinput2_end_h, M=auxinput2_end_m, S=auxinput2_end_s, rc=rc )
1331       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1332                             'WRFU_TimeIntervalSet(auxinput2_end) FAILED', &
1333                             __FILE__ , &
1334                             __LINE__  )
1335    ELSE
1336       end_time = run_length + padding_interval
1337    ENDIF
1338 
1339    CALL domain_alarm_create( grid, AUXINPUT2_ALARM, interval, begin_time, end_time )
1340 
1341    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1342      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT2_ALARM ),  rc=rc )
1343      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1344                            'WRFU_AlarmRingerOn(AUXINPUT2_ALARM) FAILED', &
1345                            __FILE__ , &
1346                            __LINE__  )
1347    ENDIF
1348 
1349 ! AUXINPUT3_ INTERVAL
1350 ! auxinput3_interval is left there (and means minutes) for consistency, but
1351 ! auxinput3_interval_m will take precedence if specified
1352    CALL nl_get_auxinput3_interval( grid%id, auxinput3_interval )   ! same as minutes
1353    CALL nl_get_auxinput3_interval_mo( grid%id, auxinput3_interval_mo )
1354    CALL nl_get_auxinput3_interval_d( grid%id, auxinput3_interval_d )
1355    CALL nl_get_auxinput3_interval_h( grid%id, auxinput3_interval_h )
1356    CALL nl_get_auxinput3_interval_m( grid%id, auxinput3_interval_m )
1357    CALL nl_get_auxinput3_interval_s( grid%id, auxinput3_interval_s )
1358    IF ( auxinput3_interval_m .EQ. 0 ) auxinput3_interval_m = auxinput3_interval
1359 
1360    IF ( MAX( auxinput3_interval_mo, auxinput3_interval_d,   &
1361              auxinput3_interval_h, auxinput3_interval_m , auxinput3_interval_s   ) .GT. 0 ) THEN
1362      CALL WRFU_TimeIntervalSet( interval, MM=auxinput3_interval_mo, D=auxinput3_interval_d, &
1363                                         H=auxinput3_interval_h, M=auxinput3_interval_m, S=auxinput3_interval_s, rc=rc )
1364      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1365                            'WRFU_TimeIntervalSet(auxinput3_interval) FAILED', &
1366                            __FILE__ , &
1367                            __LINE__  )
1368    ELSE
1369      interval = run_length + padding_interval
1370    ENDIF
1371 
1372    CALL nl_get_auxinput3_begin_y( grid%id, auxinput3_begin_y )
1373    CALL nl_get_auxinput3_begin_mo( grid%id, auxinput3_begin_mo )
1374    CALL nl_get_auxinput3_begin_d( grid%id, auxinput3_begin_d )
1375    CALL nl_get_auxinput3_begin_h( grid%id, auxinput3_begin_h )
1376    CALL nl_get_auxinput3_begin_m( grid%id, auxinput3_begin_m )
1377    CALL nl_get_auxinput3_begin_s( grid%id, auxinput3_begin_s )
1378    IF ( MAX( auxinput3_begin_y, auxinput3_begin_mo, auxinput3_begin_d,   &
1379              auxinput3_begin_h, auxinput3_begin_m , auxinput3_begin_s   ) .GT. 0 ) THEN
1380       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput3_begin_mo, D=auxinput3_begin_d, &
1381                                       H=auxinput3_begin_h, M=auxinput3_begin_m, S=auxinput3_begin_s, rc=rc )
1382       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1383                             'WRFU_TimeIntervalSet(auxinput3_begin) FAILED', &
1384                             __FILE__ , &
1385                             __LINE__  )
1386    ELSE
1387       begin_time = zero_time
1388    ENDIF
1389 
1390    CALL nl_get_auxinput3_end_y( grid%id, auxinput3_end_y )
1391    CALL nl_get_auxinput3_end_mo( grid%id, auxinput3_end_mo )
1392    CALL nl_get_auxinput3_end_d( grid%id, auxinput3_end_d )
1393    CALL nl_get_auxinput3_end_h( grid%id, auxinput3_end_h )
1394    CALL nl_get_auxinput3_end_m( grid%id, auxinput3_end_m )
1395    CALL nl_get_auxinput3_end_s( grid%id, auxinput3_end_s )
1396    IF ( MAX( auxinput3_end_y, auxinput3_end_mo, auxinput3_end_d,   &
1397              auxinput3_end_h, auxinput3_end_m , auxinput3_end_s   ) .GT. 0 ) THEN
1398       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput3_end_mo, D=auxinput3_end_d, &
1399                                      H=auxinput3_end_h, M=auxinput3_end_m, S=auxinput3_end_s, rc=rc )
1400       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1401                             'WRFU_TimeIntervalSet(auxinput3_end) FAILED', &
1402                             __FILE__ , &
1403                             __LINE__  )
1404    ELSE
1405       end_time = run_length + padding_interval
1406    ENDIF
1407 
1408    CALL domain_alarm_create( grid, AUXINPUT3_ALARM, interval, begin_time, end_time )
1409 
1410    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1411      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT3_ALARM ),  rc=rc )
1412      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1413                            'WRFU_AlarmRingerOn(AUXINPUT3_ALARM) FAILED', &
1414                            __FILE__ , &
1415                            __LINE__  )
1416    ENDIF
1417 
1418 ! AUXINPUT4_ INTERVAL
1419 ! auxinput4_interval is left there (and means minutes) for consistency, but
1420 ! auxinput4_interval_m will take precedence if specified
1421    CALL nl_get_auxinput4_interval( grid%id, auxinput4_interval )   ! same as minutes
1422    CALL nl_get_auxinput4_interval_mo( grid%id, auxinput4_interval_mo )
1423    CALL nl_get_auxinput4_interval_d( grid%id, auxinput4_interval_d )
1424    CALL nl_get_auxinput4_interval_h( grid%id, auxinput4_interval_h )
1425    CALL nl_get_auxinput4_interval_m( grid%id, auxinput4_interval_m )
1426    CALL nl_get_auxinput4_interval_s( grid%id, auxinput4_interval_s )
1427    IF ( auxinput4_interval_m .EQ. 0 ) auxinput4_interval_m = auxinput4_interval
1428 
1429    IF ( MAX( auxinput4_interval_mo, auxinput4_interval_d,   &
1430              auxinput4_interval_h, auxinput4_interval_m , auxinput4_interval_s   ) .GT. 0 ) THEN
1431      CALL WRFU_TimeIntervalSet( interval, MM=auxinput4_interval_mo, D=auxinput4_interval_d, &
1432                                         H=auxinput4_interval_h, M=auxinput4_interval_m, S=auxinput4_interval_s, rc=rc )
1433      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1434                            'WRFU_TimeIntervalSet(auxinput4_interval) FAILED', &
1435                            __FILE__ , &
1436                            __LINE__  )
1437    ELSE
1438      interval = run_length + padding_interval
1439    ENDIF
1440 
1441    CALL nl_get_auxinput4_begin_y( grid%id, auxinput4_begin_y )
1442    CALL nl_get_auxinput4_begin_mo( grid%id, auxinput4_begin_mo )
1443    CALL nl_get_auxinput4_begin_d( grid%id, auxinput4_begin_d )
1444    CALL nl_get_auxinput4_begin_h( grid%id, auxinput4_begin_h )
1445    CALL nl_get_auxinput4_begin_m( grid%id, auxinput4_begin_m )
1446    CALL nl_get_auxinput4_begin_s( grid%id, auxinput4_begin_s )
1447    IF ( MAX( auxinput4_begin_y, auxinput4_begin_mo, auxinput4_begin_d,   &
1448              auxinput4_begin_h, auxinput4_begin_m , auxinput4_begin_s   ) .GT. 0 ) THEN
1449       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput4_begin_mo, D=auxinput4_begin_d, &
1450                                       H=auxinput4_begin_h, M=auxinput4_begin_m, S=auxinput4_begin_s, rc=rc )
1451       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1452                             'WRFU_TimeIntervalSet(auxinput4_begin) FAILED', &
1453                             __FILE__ , &
1454                             __LINE__  )
1455    ELSE
1456       begin_time = zero_time
1457    ENDIF
1458 
1459    CALL nl_get_auxinput4_end_y( grid%id, auxinput4_end_y )
1460    CALL nl_get_auxinput4_end_mo( grid%id, auxinput4_end_mo )
1461    CALL nl_get_auxinput4_end_d( grid%id, auxinput4_end_d )
1462    CALL nl_get_auxinput4_end_h( grid%id, auxinput4_end_h )
1463    CALL nl_get_auxinput4_end_m( grid%id, auxinput4_end_m )
1464    CALL nl_get_auxinput4_end_s( grid%id, auxinput4_end_s )
1465    IF ( MAX( auxinput4_end_y, auxinput4_end_mo, auxinput4_end_d,   &
1466              auxinput4_end_h, auxinput4_end_m , auxinput4_end_s   ) .GT. 0 ) THEN
1467       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput4_end_mo, D=auxinput4_end_d, &
1468                                      H=auxinput4_end_h, M=auxinput4_end_m, S=auxinput4_end_s, rc=rc )
1469       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1470                             'WRFU_TimeIntervalSet(auxinput4_end) FAILED', &
1471                             __FILE__ , &
1472                             __LINE__  )
1473    ELSE
1474       end_time = run_length + padding_interval
1475    ENDIF
1476 
1477    CALL domain_alarm_create( grid, AUXINPUT4_ALARM, interval, begin_time, end_time )
1478 
1479    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1480      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT4_ALARM ),  rc=rc )
1481      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1482                            'WRFU_AlarmRingerOn(AUXINPUT4_ALARM) FAILED', &
1483                            __FILE__ , &
1484                            __LINE__  )
1485    ENDIF
1486 
1487 ! AUXINPUT5_ INTERVAL
1488 ! auxinput5_interval is left there (and means minutes) for consistency, but
1489 ! auxinput5_interval_m will take precedence if specified
1490    CALL nl_get_auxinput5_interval( grid%id, auxinput5_interval )   ! same as minutes
1491    CALL nl_get_auxinput5_interval_mo( grid%id, auxinput5_interval_mo )
1492    CALL nl_get_auxinput5_interval_d( grid%id, auxinput5_interval_d )
1493    CALL nl_get_auxinput5_interval_h( grid%id, auxinput5_interval_h )
1494    CALL nl_get_auxinput5_interval_m( grid%id, auxinput5_interval_m )
1495    CALL nl_get_auxinput5_interval_s( grid%id, auxinput5_interval_s )
1496    IF ( auxinput5_interval_m .EQ. 0 ) auxinput5_interval_m = auxinput5_interval
1497 
1498    IF ( MAX( auxinput5_interval_mo, auxinput5_interval_d,   &
1499              auxinput5_interval_h, auxinput5_interval_m , auxinput5_interval_s   ) .GT. 0 ) THEN
1500      CALL WRFU_TimeIntervalSet( interval, MM=auxinput5_interval_mo, D=auxinput5_interval_d, &
1501                                         H=auxinput5_interval_h, M=auxinput5_interval_m, S=auxinput5_interval_s, rc=rc )
1502      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1503                            'WRFU_TimeIntervalSet(auxinput5_interval) FAILED', &
1504                            __FILE__ , &
1505                            __LINE__  )
1506    ELSE
1507      interval = run_length + padding_interval
1508    ENDIF
1509 
1510    CALL nl_get_auxinput5_begin_y( grid%id, auxinput5_begin_y )
1511    CALL nl_get_auxinput5_begin_mo( grid%id, auxinput5_begin_mo )
1512    CALL nl_get_auxinput5_begin_d( grid%id, auxinput5_begin_d )
1513    CALL nl_get_auxinput5_begin_h( grid%id, auxinput5_begin_h )
1514    CALL nl_get_auxinput5_begin_m( grid%id, auxinput5_begin_m )
1515    CALL nl_get_auxinput5_begin_s( grid%id, auxinput5_begin_s )
1516    IF ( MAX( auxinput5_begin_y, auxinput5_begin_mo, auxinput5_begin_d,   &
1517              auxinput5_begin_h, auxinput5_begin_m , auxinput5_begin_s   ) .GT. 0 ) THEN
1518       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput5_begin_mo, D=auxinput5_begin_d, &
1519                                       H=auxinput5_begin_h, M=auxinput5_begin_m, S=auxinput5_begin_s, rc=rc )
1520       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1521                             'WRFU_TimeIntervalSet(auxinput5_begin) FAILED', &
1522                             __FILE__ , &
1523                             __LINE__  )
1524    ELSE
1525       begin_time = zero_time
1526    ENDIF
1527 
1528    CALL nl_get_auxinput5_end_y( grid%id, auxinput5_end_y )
1529    CALL nl_get_auxinput5_end_mo( grid%id, auxinput5_end_mo )
1530    CALL nl_get_auxinput5_end_d( grid%id, auxinput5_end_d )
1531    CALL nl_get_auxinput5_end_h( grid%id, auxinput5_end_h )
1532    CALL nl_get_auxinput5_end_m( grid%id, auxinput5_end_m )
1533    CALL nl_get_auxinput5_end_s( grid%id, auxinput5_end_s )
1534    IF ( MAX( auxinput5_end_y, auxinput5_end_mo, auxinput5_end_d,   &
1535              auxinput5_end_h, auxinput5_end_m , auxinput5_end_s   ) .GT. 0 ) THEN
1536       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput5_end_mo, D=auxinput5_end_d, &
1537                                      H=auxinput5_end_h, M=auxinput5_end_m, S=auxinput5_end_s, rc=rc )
1538       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1539                             'WRFU_TimeIntervalSet(auxinput5_end) FAILED', &
1540                             __FILE__ , &
1541                             __LINE__  )
1542    ELSE
1543       end_time = run_length + padding_interval
1544    ENDIF
1545 
1546    CALL domain_alarm_create( grid, AUXINPUT5_ALARM, interval, begin_time, end_time )
1547 
1548 !TBH:  Should be OK to remove the "#else" section and the code it contains 
1549 !TBH:  because later code overwrites grid%alarms( AUXINPUT5_ALARM )...  
1550 !TBH:  In fact, by setting namelist values for auxinput5 correctly, it ought 
1551 !TBH:  to be possible to get rid of all "#ifdef WRF_CHEM" bits in this file...  
1552 #ifndef WRF_CHEM
1553    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1554      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT5_ALARM ),  rc=rc )
1555      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1556                            'WRFU_AlarmRingerOn(AUXINPUT5_ALARM) FAILED', &
1557                            __FILE__ , &
1558                            __LINE__  )
1559    ENDIF
1560 #else
1561    CALL WRFU_AlarmEnable( grid%alarms( AUXINPUT5_ALARM ), rc=rc )
1562    CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT5_ALARM ), rc=rc )
1563 #endif
1564 
1565 
1566    CALL domain_alarm_create( grid, BOUNDARY_ALARM )
1567 
1568    CALL WRFU_AlarmEnable( grid%alarms( BOUNDARY_ALARM ), rc=rc )
1569    CALL wrf_check_error( WRFU_SUCCESS, rc, &
1570                          'WRFU_AlarmEnable(BOUNDARY_ALARM) FAILED', &
1571                          __FILE__ , &
1572                          __LINE__  )
1573    CALL WRFU_AlarmRingerOn( grid%alarms( BOUNDARY_ALARM ), rc=rc )
1574    CALL wrf_check_error( WRFU_SUCCESS, rc, &
1575                          'WRFU_AlarmRingerOn(BOUNDARY_ALARM) FAILED', &
1576                          __FILE__ , &
1577                          __LINE__  )
1578 
1579 #ifdef WRF_CHEM
1580 ! TBH:  NOTE:  Proper setting of namelist variables for auxinput5 ought to 
1581 ! TBH:         make this hard-coded bit unnecessary.  
1582 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1583 ! add for wrf_chem emiss input
1584    CALL WRFU_AlarmEnable( grid%alarms( AUXINPUT5_ALARM ), rc=rc )
1585    CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT5_ALARM ), rc=rc )
1586 ! end for wrf chem emiss input
1587 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
1588 #endif
1589 
1590 ! AUXINPUT6_ INTERVAL
1591 ! auxinput6_interval is left there (and means minutes) for consistency, but
1592 ! auxinput6_interval_m will take precedence if specified
1593    CALL nl_get_auxinput6_interval( grid%id, auxinput6_interval )   ! same as minutes
1594    CALL nl_get_auxinput6_interval_mo( grid%id, auxinput6_interval_mo )
1595    CALL nl_get_auxinput6_interval_d( grid%id, auxinput6_interval_d )
1596    CALL nl_get_auxinput6_interval_h( grid%id, auxinput6_interval_h )
1597    CALL nl_get_auxinput6_interval_m( grid%id, auxinput6_interval_m )
1598    CALL nl_get_auxinput6_interval_s( grid%id, auxinput6_interval_s )
1599    IF ( auxinput6_interval_m .EQ. 0 ) auxinput6_interval_m = auxinput6_interval
1600 
1601    IF ( MAX( auxinput6_interval_mo, auxinput6_interval_d,   &
1602              auxinput6_interval_h, auxinput6_interval_m , auxinput6_interval_s   ) .GT. 0 ) THEN
1603      CALL WRFU_TimeIntervalSet( interval, MM=auxinput6_interval_mo, D=auxinput6_interval_d, &
1604                                         H=auxinput6_interval_h, M=auxinput6_interval_m, S=auxinput6_interval_s, rc=rc )
1605      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1606                            'WRFU_TimeIntervalSet(auxinput6_interval) FAILED', &
1607                            __FILE__ , &
1608                            __LINE__  )
1609    ELSE
1610      interval = run_length + padding_interval
1611    ENDIF
1612 
1613    CALL nl_get_auxinput6_begin_y( grid%id, auxinput6_begin_y )
1614    CALL nl_get_auxinput6_begin_mo( grid%id, auxinput6_begin_mo )
1615    CALL nl_get_auxinput6_begin_d( grid%id, auxinput6_begin_d )
1616    CALL nl_get_auxinput6_begin_h( grid%id, auxinput6_begin_h )
1617    CALL nl_get_auxinput6_begin_m( grid%id, auxinput6_begin_m )
1618    CALL nl_get_auxinput6_begin_s( grid%id, auxinput6_begin_s )
1619    IF ( MAX( auxinput6_begin_y, auxinput6_begin_mo, auxinput6_begin_d,   &
1620              auxinput6_begin_h, auxinput6_begin_m , auxinput6_begin_s   ) .GT. 0 ) THEN
1621       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput6_begin_mo, D=auxinput6_begin_d, &
1622                                       H=auxinput6_begin_h, M=auxinput6_begin_m, S=auxinput6_begin_s, rc=rc )
1623       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1624                             'WRFU_TimeIntervalSet(auxinput6_begin) FAILED', &
1625                             __FILE__ , &
1626                             __LINE__  )
1627    ELSE
1628       begin_time = zero_time
1629    ENDIF
1630 
1631    CALL nl_get_auxinput6_end_y( grid%id, auxinput6_end_y )
1632    CALL nl_get_auxinput6_end_mo( grid%id, auxinput6_end_mo )
1633    CALL nl_get_auxinput6_end_d( grid%id, auxinput6_end_d )
1634    CALL nl_get_auxinput6_end_h( grid%id, auxinput6_end_h )
1635    CALL nl_get_auxinput6_end_m( grid%id, auxinput6_end_m )
1636    CALL nl_get_auxinput6_end_s( grid%id, auxinput6_end_s )
1637    IF ( MAX( auxinput6_end_y, auxinput6_end_mo, auxinput6_end_d,   &
1638              auxinput6_end_h, auxinput6_end_m , auxinput6_end_s   ) .GT. 0 ) THEN
1639       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput6_end_mo, D=auxinput6_end_d, &
1640                                      H=auxinput6_end_h, M=auxinput6_end_m, S=auxinput6_end_s, rc=rc )
1641       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1642                             'WRFU_TimeIntervalSet(auxinput6_end) FAILED', &
1643                             __FILE__ , &
1644                             __LINE__  )
1645    ELSE
1646       end_time = run_length + padding_interval
1647    ENDIF
1648 
1649    CALL domain_alarm_create( grid, AUXINPUT6_ALARM, interval, begin_time, end_time )
1650 
1651    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1652      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT6_ALARM ),  rc=rc )
1653      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1654                            'WRFU_AlarmRingerOn(AUXINPUT6_ALARM) FAILED', &
1655                            __FILE__ , &
1656                            __LINE__  )
1657    ENDIF
1658 
1659 
1660 ! AUXINPUT7_ INTERVAL
1661 ! auxinput7_interval is left there (and means minutes) for consistency, but
1662 ! auxinput7_interval_m will take precedence if specified
1663    CALL nl_get_auxinput7_interval( grid%id, auxinput7_interval )   ! same as minutes
1664    CALL nl_get_auxinput7_interval_mo( grid%id, auxinput7_interval_mo )
1665    CALL nl_get_auxinput7_interval_d( grid%id, auxinput7_interval_d )
1666    CALL nl_get_auxinput7_interval_h( grid%id, auxinput7_interval_h )
1667    CALL nl_get_auxinput7_interval_m( grid%id, auxinput7_interval_m )
1668    CALL nl_get_auxinput7_interval_s( grid%id, auxinput7_interval_s )
1669    IF ( auxinput7_interval_m .EQ. 0 ) auxinput7_interval_m = auxinput7_interval
1670 
1671    IF ( MAX( auxinput7_interval_mo, auxinput7_interval_d,   &
1672              auxinput7_interval_h, auxinput7_interval_m , auxinput7_interval_s   ) .GT. 0 ) THEN
1673      CALL WRFU_TimeIntervalSet( interval, MM=auxinput7_interval_mo, D=auxinput7_interval_d, &
1674                                         H=auxinput7_interval_h, M=auxinput7_interval_m, S=auxinput7_interval_s, rc=rc )
1675      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1676                            'WRFU_TimeIntervalSet(auxinput7_interval) FAILED', &
1677                            __FILE__ , &
1678                            __LINE__  )
1679    ELSE
1680      interval = run_length + padding_interval
1681    ENDIF
1682 
1683    CALL nl_get_auxinput7_begin_y( grid%id, auxinput7_begin_y )
1684    CALL nl_get_auxinput7_begin_mo( grid%id, auxinput7_begin_mo )
1685    CALL nl_get_auxinput7_begin_d( grid%id, auxinput7_begin_d )
1686    CALL nl_get_auxinput7_begin_h( grid%id, auxinput7_begin_h )
1687    CALL nl_get_auxinput7_begin_m( grid%id, auxinput7_begin_m )
1688    CALL nl_get_auxinput7_begin_s( grid%id, auxinput7_begin_s )
1689    IF ( MAX( auxinput7_begin_y, auxinput7_begin_mo, auxinput7_begin_d,   &
1690              auxinput7_begin_h, auxinput7_begin_m , auxinput7_begin_s   ) .GT. 0 ) THEN
1691       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput7_begin_mo, D=auxinput7_begin_d, &
1692                                       H=auxinput7_begin_h, M=auxinput7_begin_m, S=auxinput7_begin_s, rc=rc )
1693       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1694                             'WRFU_TimeIntervalSet(auxinput7_begin) FAILED', &
1695                             __FILE__ , &
1696                             __LINE__  )
1697    ELSE
1698       begin_time = zero_time
1699    ENDIF
1700 
1701    CALL nl_get_auxinput7_end_y( grid%id, auxinput7_end_y )
1702    CALL nl_get_auxinput7_end_mo( grid%id, auxinput7_end_mo )
1703    CALL nl_get_auxinput7_end_d( grid%id, auxinput7_end_d )
1704    CALL nl_get_auxinput7_end_h( grid%id, auxinput7_end_h )
1705    CALL nl_get_auxinput7_end_m( grid%id, auxinput7_end_m )
1706    CALL nl_get_auxinput7_end_s( grid%id, auxinput7_end_s )
1707    IF ( MAX( auxinput7_end_y, auxinput7_end_mo, auxinput7_end_d,   &
1708              auxinput7_end_h, auxinput7_end_m , auxinput7_end_s   ) .GT. 0 ) THEN
1709       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput7_end_mo, D=auxinput7_end_d, &
1710                                      H=auxinput7_end_h, M=auxinput7_end_m, S=auxinput7_end_s, rc=rc )
1711       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1712                             'WRFU_TimeIntervalSet(auxinput7_end) FAILED', &
1713                             __FILE__ , &
1714                             __LINE__  )
1715    ELSE
1716       end_time = run_length + padding_interval
1717    ENDIF
1718 
1719    CALL domain_alarm_create( grid, AUXINPUT7_ALARM, interval, begin_time, end_time )
1720 
1721    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1722      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT7_ALARM ),  rc=rc )
1723      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1724                            'WRFU_AlarmRingerOn(AUXINPUT7_ALARM) FAILED', &
1725                            __FILE__ , &
1726                            __LINE__  )
1727    ENDIF
1728 
1729 
1730 
1731 ! AUXINPUT8_ INTERVAL
1732 ! auxinput8_interval is left there (and means minutes) for consistency, but
1733 ! auxinput8_interval_m will take precedence if specified
1734    CALL nl_get_auxinput8_interval( grid%id, auxinput8_interval )   ! same as minutes
1735    CALL nl_get_auxinput8_interval_mo( grid%id, auxinput8_interval_mo )
1736    CALL nl_get_auxinput8_interval_d( grid%id, auxinput8_interval_d )
1737    CALL nl_get_auxinput8_interval_h( grid%id, auxinput8_interval_h )
1738    CALL nl_get_auxinput8_interval_m( grid%id, auxinput8_interval_m )
1739    CALL nl_get_auxinput8_interval_s( grid%id, auxinput8_interval_s )
1740    IF ( auxinput8_interval_m .EQ. 0 ) auxinput8_interval_m = auxinput8_interval
1741 
1742    IF ( MAX( auxinput8_interval_mo, auxinput8_interval_d,   &
1743              auxinput8_interval_h, auxinput8_interval_m , auxinput8_interval_s   ) .GT. 0 ) THEN
1744      CALL WRFU_TimeIntervalSet( interval, MM=auxinput8_interval_mo, D=auxinput8_interval_d, &
1745                                         H=auxinput8_interval_h, M=auxinput8_interval_m, S=auxinput8_interval_s, rc=rc )
1746      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1747                            'WRFU_TimeIntervalSet(auxinput8_interval) FAILED', &
1748                            __FILE__ , &
1749                            __LINE__  )
1750    ELSE
1751      interval = run_length + padding_interval
1752    ENDIF
1753 
1754    CALL nl_get_auxinput8_begin_y( grid%id, auxinput8_begin_y )
1755    CALL nl_get_auxinput8_begin_mo( grid%id, auxinput8_begin_mo )
1756    CALL nl_get_auxinput8_begin_d( grid%id, auxinput8_begin_d )
1757    CALL nl_get_auxinput8_begin_h( grid%id, auxinput8_begin_h )
1758    CALL nl_get_auxinput8_begin_m( grid%id, auxinput8_begin_m )
1759    CALL nl_get_auxinput8_begin_s( grid%id, auxinput8_begin_s )
1760    IF ( MAX( auxinput8_begin_y, auxinput8_begin_mo, auxinput8_begin_d,   &
1761              auxinput8_begin_h, auxinput8_begin_m , auxinput8_begin_s   ) .GT. 0 ) THEN
1762       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput8_begin_mo, D=auxinput8_begin_d, &
1763                                       H=auxinput8_begin_h, M=auxinput8_begin_m, S=auxinput8_begin_s, rc=rc )
1764       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1765                             'WRFU_TimeIntervalSet(auxinput8_begin) FAILED', &
1766                             __FILE__ , &
1767                             __LINE__  )
1768    ELSE
1769       begin_time = zero_time
1770    ENDIF
1771 
1772    CALL nl_get_auxinput8_end_y( grid%id, auxinput8_end_y )
1773    CALL nl_get_auxinput8_end_mo( grid%id, auxinput8_end_mo )
1774    CALL nl_get_auxinput8_end_d( grid%id, auxinput8_end_d )
1775    CALL nl_get_auxinput8_end_h( grid%id, auxinput8_end_h )
1776    CALL nl_get_auxinput8_end_m( grid%id, auxinput8_end_m )
1777    CALL nl_get_auxinput8_end_s( grid%id, auxinput8_end_s )
1778    IF ( MAX( auxinput8_end_y, auxinput8_end_mo, auxinput8_end_d,   &
1779              auxinput8_end_h, auxinput8_end_m , auxinput8_end_s   ) .GT. 0 ) THEN
1780       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput8_end_mo, D=auxinput8_end_d, &
1781                                      H=auxinput8_end_h, M=auxinput8_end_m, S=auxinput8_end_s, rc=rc )
1782       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1783                             'WRFU_TimeIntervalSet(auxinput8_end) FAILED', &
1784                             __FILE__ , &
1785                             __LINE__  )
1786    ELSE
1787       end_time = run_length + padding_interval
1788    ENDIF
1789 
1790    CALL domain_alarm_create( grid, AUXINPUT8_ALARM, interval, begin_time, end_time )
1791 
1792    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1793      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT8_ALARM ),  rc=rc )
1794      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1795                            'WRFU_AlarmRingerOn(AUXINPUT8_ALARM) FAILED', &
1796                            __FILE__ , &
1797                            __LINE__  )
1798    ENDIF
1799 
1800 ! AUXINPUT9_ INTERVAL
1801 ! auxinput9_interval is left there (and means minutes) for consistency, but
1802 ! auxinput9_interval_m will take precedence if specified
1803    CALL nl_get_auxinput9_interval( grid%id, auxinput9_interval )   ! same as minutes
1804    CALL nl_get_auxinput9_interval_mo( grid%id, auxinput9_interval_mo )
1805    CALL nl_get_auxinput9_interval_d( grid%id, auxinput9_interval_d )
1806    CALL nl_get_auxinput9_interval_h( grid%id, auxinput9_interval_h )
1807    CALL nl_get_auxinput9_interval_m( grid%id, auxinput9_interval_m )
1808    CALL nl_get_auxinput9_interval_s( grid%id, auxinput9_interval_s )
1809    IF ( auxinput9_interval_m .EQ. 0 ) auxinput9_interval_m = auxinput9_interval
1810 
1811    IF ( MAX( auxinput9_interval_mo, auxinput9_interval_d,   &
1812              auxinput9_interval_h, auxinput9_interval_m , auxinput9_interval_s   ) .GT. 0 ) THEN
1813      CALL WRFU_TimeIntervalSet( interval, MM=auxinput9_interval_mo, D=auxinput9_interval_d, &
1814                                         H=auxinput9_interval_h, M=auxinput9_interval_m, S=auxinput9_interval_s, rc=rc )
1815      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1816                            'WRFU_TimeIntervalSet(auxinput9_interval) FAILED', &
1817                            __FILE__ , &
1818                            __LINE__  )
1819    ELSE
1820      interval = run_length + padding_interval
1821    ENDIF
1822 
1823    CALL nl_get_auxinput9_begin_y( grid%id, auxinput9_begin_y )
1824    CALL nl_get_auxinput9_begin_mo( grid%id, auxinput9_begin_mo )
1825    CALL nl_get_auxinput9_begin_d( grid%id, auxinput9_begin_d )
1826    CALL nl_get_auxinput9_begin_h( grid%id, auxinput9_begin_h )
1827    CALL nl_get_auxinput9_begin_m( grid%id, auxinput9_begin_m )
1828    CALL nl_get_auxinput9_begin_s( grid%id, auxinput9_begin_s )
1829    IF ( MAX( auxinput9_begin_y, auxinput9_begin_mo, auxinput9_begin_d,   &
1830              auxinput9_begin_h, auxinput9_begin_m , auxinput9_begin_s   ) .GT. 0 ) THEN
1831       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput9_begin_mo, D=auxinput9_begin_d, &
1832                                       H=auxinput9_begin_h, M=auxinput9_begin_m, S=auxinput9_begin_s, rc=rc )
1833       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1834                             'WRFU_TimeIntervalSet(auxinput9_begin) FAILED', &
1835                             __FILE__ , &
1836                             __LINE__  )
1837    ELSE
1838       begin_time = zero_time
1839    ENDIF
1840 
1841    CALL nl_get_auxinput9_end_y( grid%id, auxinput9_end_y )
1842    CALL nl_get_auxinput9_end_mo( grid%id, auxinput9_end_mo )
1843    CALL nl_get_auxinput9_end_d( grid%id, auxinput9_end_d )
1844    CALL nl_get_auxinput9_end_h( grid%id, auxinput9_end_h )
1845    CALL nl_get_auxinput9_end_m( grid%id, auxinput9_end_m )
1846    CALL nl_get_auxinput9_end_s( grid%id, auxinput9_end_s )
1847    IF ( MAX( auxinput9_end_y, auxinput9_end_mo, auxinput9_end_d,   &
1848              auxinput9_end_h, auxinput9_end_m , auxinput9_end_s   ) .GT. 0 ) THEN
1849       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput9_end_mo, D=auxinput9_end_d, &
1850                                      H=auxinput9_end_h, M=auxinput9_end_m, S=auxinput9_end_s, rc=rc )
1851       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1852                             'WRFU_TimeIntervalSet(auxinput9_end) FAILED', &
1853                             __FILE__ , &
1854                             __LINE__  )
1855    ELSE
1856       end_time = run_length + padding_interval
1857    ENDIF
1858 
1859    CALL domain_alarm_create( grid, AUXINPUT9_ALARM, interval, begin_time, end_time )
1860 
1861    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1862      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT9_ALARM ),  rc=rc )
1863      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1864                            'WRFU_AlarmRingerOn(AUXINPUT9_ALARM) FAILED', &
1865                            __FILE__ , &
1866                            __LINE__  )
1867    ENDIF
1868 
1869 #if (EM_CORE == 1)
1870   CALL nl_get_grid_fdda( grid%id, grid_fdda )
1871 #endif
1872 
1873 ! AUXINPUT10_ INTERVAL (GFDDA)
1874 ! gfdda_interval is left there (and means minutes) for consistency, but
1875 ! gfdda_interval_m will take precedence if specified
1876    CALL nl_get_gfdda_interval( grid%id, gfdda_interval )   ! same as minutes
1877    CALL nl_get_gfdda_interval_mo( grid%id, gfdda_interval_mo )
1878    CALL nl_get_gfdda_interval_d( grid%id, gfdda_interval_d )
1879    CALL nl_get_gfdda_interval_h( grid%id, gfdda_interval_h )
1880    CALL nl_get_gfdda_interval_m( grid%id, gfdda_interval_m )
1881    CALL nl_get_gfdda_interval_s( grid%id, gfdda_interval_s )
1882    IF ( gfdda_interval_m .EQ. 0 ) gfdda_interval_m = gfdda_interval
1883 
1884    IF ( MAX( gfdda_interval_mo, gfdda_interval_d,   &
1885              gfdda_interval_h, gfdda_interval_m , gfdda_interval_s   ) .GT. 0 ) THEN
1886      CALL WRFU_TimeIntervalSet( interval, MM=gfdda_interval_mo, D=gfdda_interval_d, &
1887                                         H=gfdda_interval_h, M=gfdda_interval_m, S=gfdda_interval_s, rc=rc )
1888      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1889                            'WRFU_TimeIntervalSet(gfdda_interval) FAILED', &
1890                            __FILE__ , &
1891                            __LINE__  )
1892    ELSE
1893      interval = run_length + padding_interval
1894    ENDIF
1895 #if (EM_CORE == 1)
1896    IF( grid_fdda == 0 ) interval = run_length + padding_interval
1897 #endif
1898 
1899    CALL nl_get_gfdda_begin_y( grid%id, gfdda_begin_y )
1900    CALL nl_get_gfdda_begin_mo( grid%id, gfdda_begin_mo )
1901    CALL nl_get_gfdda_begin_d( grid%id, gfdda_begin_d )
1902    CALL nl_get_gfdda_begin_h( grid%id, gfdda_begin_h )
1903    CALL nl_get_gfdda_begin_m( grid%id, gfdda_begin_m )
1904    CALL nl_get_gfdda_begin_s( grid%id, gfdda_begin_s )
1905    IF ( MAX( gfdda_begin_y, gfdda_begin_mo, gfdda_begin_d,   &
1906              gfdda_begin_h, gfdda_begin_m , gfdda_begin_s   ) .GT. 0 ) THEN
1907       CALL WRFU_TimeIntervalSet( begin_time , MM=gfdda_begin_mo, D=gfdda_begin_d, &
1908                                       H=gfdda_begin_h, M=gfdda_begin_m, S=gfdda_begin_s, rc=rc )
1909       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1910                             'WRFU_TimeIntervalSet(gfdda_begin) FAILED', &
1911                             __FILE__ , &
1912                             __LINE__  )
1913    ELSE
1914       begin_time = zero_time
1915    ENDIF
1916 
1917    CALL nl_get_gfdda_end_y( grid%id, gfdda_end_y )
1918    CALL nl_get_gfdda_end_mo( grid%id, gfdda_end_mo )
1919    CALL nl_get_gfdda_end_d( grid%id, gfdda_end_d )
1920    CALL nl_get_gfdda_end_h( grid%id, gfdda_end_h )
1921 #if (EM_CORE == 1)
1922    IF( grid_fdda == 1 ) gfdda_end_h = gfdda_end_h - NINT( gfdda_interval_m/60.0 )
1923 #endif
1924    CALL nl_get_gfdda_end_m( grid%id, gfdda_end_m )
1925    CALL nl_get_gfdda_end_s( grid%id, gfdda_end_s )
1926    IF ( MAX( gfdda_end_y, gfdda_end_mo, gfdda_end_d,   &
1927              gfdda_end_h, gfdda_end_m , gfdda_end_s   ) .GT. 0 ) THEN
1928       CALL WRFU_TimeIntervalSet( end_time , MM=gfdda_end_mo, D=gfdda_end_d, &
1929                                      H=gfdda_end_h, M=gfdda_end_m, S=gfdda_end_s, rc=rc )
1930       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1931                             'WRFU_TimeIntervalSet(gfdda_end) FAILED', &
1932                             __FILE__ , &
1933                             __LINE__  )
1934    ELSE
1935       end_time = run_length + padding_interval
1936    ENDIF
1937 #if (EM_CORE == 1)
1938    IF( grid_fdda == 0 ) end_time = run_length + padding_interval
1939 #endif
1940 
1941    CALL domain_alarm_create( grid, AUXINPUT10_ALARM, interval, begin_time, end_time )
1942 
1943    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
1944      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT10_ALARM ),  rc=rc )
1945      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1946                            'WRFU_AlarmRingerOn(AUXINPUT10_ALARM) FAILED', &
1947                            __FILE__ , &
1948                            __LINE__  )
1949    ENDIF
1950 
1951 ! AUXINPUT11_ INTERVAL
1952 ! auxinput11_interval is left there (and means minutes) for consistency, but
1953 ! auxinput11_interval_m will take precedence if specified
1954    CALL nl_get_auxinput11_interval( grid%id, auxinput11_interval )   ! same as minutes
1955    CALL nl_get_auxinput11_interval_mo( grid%id, auxinput11_interval_mo )
1956    CALL nl_get_auxinput11_interval_d( grid%id, auxinput11_interval_d )
1957    CALL nl_get_auxinput11_interval_h( grid%id, auxinput11_interval_h )
1958    CALL nl_get_auxinput11_interval_m( grid%id, auxinput11_interval_m )
1959    CALL nl_get_auxinput11_interval_s( grid%id, auxinput11_interval_s )
1960    IF ( auxinput11_interval_m .EQ. 0 ) auxinput11_interval_m = auxinput11_interval
1961 
1962    IF ( MAX( auxinput11_interval_mo, auxinput11_interval_d,   &
1963              auxinput11_interval_h, auxinput11_interval_m , auxinput11_interval_s   ) .GT. 0 ) THEN
1964      CALL WRFU_TimeIntervalSet( interval, MM=auxinput11_interval_mo, D=auxinput11_interval_d, &
1965                                         H=auxinput11_interval_h, M=auxinput11_interval_m, S=auxinput11_interval_s, rc=rc )
1966      CALL wrf_check_error( WRFU_SUCCESS, rc, &
1967                            'WRFU_TimeIntervalSet(auxinput11_interval) FAILED', &
1968                            __FILE__ , &
1969                            __LINE__  )
1970    ELSE
1971      interval = run_length + padding_interval
1972    ENDIF
1973 
1974    CALL nl_get_auxinput11_begin_y( grid%id, auxinput11_begin_y )
1975    CALL nl_get_auxinput11_begin_mo( grid%id, auxinput11_begin_mo )
1976    CALL nl_get_auxinput11_begin_d( grid%id, auxinput11_begin_d )
1977    CALL nl_get_auxinput11_begin_h( grid%id, auxinput11_begin_h )
1978    CALL nl_get_auxinput11_begin_m( grid%id, auxinput11_begin_m )
1979    CALL nl_get_auxinput11_begin_s( grid%id, auxinput11_begin_s )
1980    IF ( MAX( auxinput11_begin_y, auxinput11_begin_mo, auxinput11_begin_d,   &
1981              auxinput11_begin_h, auxinput11_begin_m , auxinput11_begin_s   ) .GT. 0 ) THEN
1982       CALL WRFU_TimeIntervalSet( begin_time , MM=auxinput11_begin_mo, D=auxinput11_begin_d, &
1983                                       H=auxinput11_begin_h, M=auxinput11_begin_m, S=auxinput11_begin_s, rc=rc )
1984       CALL wrf_check_error( WRFU_SUCCESS, rc, &
1985                             'WRFU_TimeIntervalSet(auxinput11_begin) FAILED', &
1986                             __FILE__ , &
1987                             __LINE__  )
1988    ELSE
1989       begin_time = zero_time
1990    ENDIF
1991 
1992    CALL nl_get_auxinput11_end_y( grid%id, auxinput11_end_y )
1993    CALL nl_get_auxinput11_end_mo( grid%id, auxinput11_end_mo )
1994    CALL nl_get_auxinput11_end_d( grid%id, auxinput11_end_d )
1995    CALL nl_get_auxinput11_end_h( grid%id, auxinput11_end_h )
1996    CALL nl_get_auxinput11_end_m( grid%id, auxinput11_end_m )
1997    CALL nl_get_auxinput11_end_s( grid%id, auxinput11_end_s )
1998    IF ( MAX( auxinput11_end_y, auxinput11_end_mo, auxinput11_end_d,   &
1999              auxinput11_end_h, auxinput11_end_m , auxinput11_end_s   ) .GT. 0 ) THEN
2000       CALL WRFU_TimeIntervalSet( end_time , MM=auxinput11_end_mo, D=auxinput11_end_d, &
2001                                      H=auxinput11_end_h, M=auxinput11_end_m, S=auxinput11_end_s, rc=rc )
2002       CALL wrf_check_error( WRFU_SUCCESS, rc, &
2003                             'WRFU_TimeIntervalSet(auxinput11_end) FAILED', &
2004                             __FILE__ , &
2005                             __LINE__  )
2006    ELSE
2007       end_time = run_length + padding_interval
2008    ENDIF
2009 
2010    CALL domain_alarm_create( grid, AUXINPUT11_ALARM, interval, begin_time, end_time )
2011 
2012    IF ( interval .NE. run_length + padding_interval .AND. begin_time .EQ. zero_time ) THEN
2013      CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT11_ALARM ),  rc=rc )
2014      CALL wrf_check_error( WRFU_SUCCESS, rc, &
2015                            'WRFU_AlarmRingerOn(AUXINPUT11_ALARM) FAILED', &
2016                            __FILE__ , &
2017                            __LINE__  )
2018    ENDIF
2019 
2020 #ifdef MOVE_NESTS
2021 ! This is the interval at which the code in time_for_move in share/mediation_integrate.F
2022 ! will recompute the center of the Vortex.  Other times, it will use the last position.
2023 !
2024    CALL nl_get_vortex_interval ( grid%id , vortex_interval ) 
2025    CALL WRFU_TimeIntervalSet( interval, M=vortex_interval, rc=rc )
2026    CALL wrf_check_error( WRFU_SUCCESS, rc, &
2027                            'WRFU_TimeIntervalSet(interval) for computing vortex center FAILED', &
2028                            __FILE__ , &
2029                            __LINE__  )
2030    CALL domain_alarm_create( grid,  COMPUTE_VORTEX_CENTER_ALARM, interval  )
2031    CALL WRFU_AlarmEnable( grid%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
2032    CALL wrf_check_error( WRFU_SUCCESS, rc, &
2033                          'WRFU_AlarmEnable(COMPUTE_VORTEX_CENTER_ALARM) FAILED', &
2034                          __FILE__ , &
2035                          __LINE__  )
2036    CALL WRFU_AlarmRingerOn( grid%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
2037    CALL wrf_check_error( WRFU_SUCCESS, rc, &
2038                          'WRFU_AlarmRingerOn(COMPUTE_VORTEX_CENTER_ALARM) FAILED', &
2039                          __FILE__ , &
2040                          __LINE__  )
2041 #endif
2042 
2043    grid%time_set = .TRUE.
2044 
2045    ! Initialize derived time quantities in grid state.  
2046    ! These are updated in domain_clockadvance().  
2047    CALL domain_clock_get( grid, minutesSinceSimulationStart=grid%xtime )
2048    CALL domain_clock_get( grid, currentDayOfYearReal=grid%julian )
2049    WRITE(wrf_err_message,*) 'setup_timekeeping:  set xtime to ',grid%xtime
2050    CALL wrf_debug ( 100, TRIM(wrf_err_message) )
2051    WRITE(wrf_err_message,*) 'setup_timekeeping:  set julian to ',grid%julian
2052    CALL wrf_debug ( 100, TRIM(wrf_err_message) )
2053 
2054    CALL wrf_debug ( 100 , 'setup_timekeeping:  returning...' )
2055 
2056 END SUBROUTINE Setup_Timekeeping
2057 
2058