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