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