source: trunk/WRF.COMMON/WRFV3/share/set_timekeeping.F @ 3567

Last change on this file since 3567 was 2759, checked in by aslmd, 2 years ago

adding unmodified code from WRFV3.0.1.1, expurged from useless data +1M size

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