updated top-level README and version_decl for V4.4.2 (#1795)
[WRF.git] / share / set_timekeeping.F
blobbd52b7184e72dd2097a41678a6c94d51481da86f
1 SUBROUTINE Setup_Timekeeping ( grid )
2    USE module_domain
3    USE module_configure
4    USE module_utility
5    IMPLICIT NONE
6    TYPE(domain), POINTER :: grid
7 ! Local
8    TYPE(WRFU_TimeInterval) :: begin_time, end_time, zero_time, one_minute, one_hour, forever, 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
17 ! #if (EM_CORE == 1)
18    INTEGER :: dfi_fwdstop_year,dfi_fwdstop_month,dfi_fwdstop_day,dfi_fwdstop_hour,dfi_fwdstop_minute,dfi_fwdstop_second
19    INTEGER :: dfi_bckstop_year,dfi_bckstop_month,dfi_bckstop_day,dfi_bckstop_hour,dfi_bckstop_minute,dfi_bckstop_second
20 ! #endif
22    INTEGER :: restart_interval_d
23    INTEGER :: inputout_interval_d
24    INTEGER :: inputout_begin_y
25    INTEGER :: inputout_end_y
26    INTEGER :: inputout_begin_m
27    INTEGER :: inputout_begin_s
28    INTEGER :: inputout_begin_d
29    INTEGER :: inputout_begin_h
30    INTEGER :: inputout_end_m
31    INTEGER :: inputout_end_s
32    INTEGER :: inputout_end_d
33    INTEGER :: inputout_end_h
34    INTEGER :: restart_interval_m
35    INTEGER :: restart_interval_s
36    INTEGER :: restart_interval
37    INTEGER :: restart_interval_h
38    INTEGER :: inputout_interval_m
39    INTEGER :: inputout_interval_s
40    INTEGER :: inputout_interval
41    INTEGER :: inputout_interval_h
43 #  include "set_timekeeping_defs.inc"
45    INTEGER :: grid_fdda, grid_sfdda
47    INTEGER :: run_days, run_hours, run_minutes, run_seconds
48    INTEGER :: time_step, time_step_fract_num, time_step_fract_den
49    INTEGER :: rc
50    REAL    :: dt
52    CALL WRFU_TimeIntervalSet ( zero_time, rc=rc )
53    CALL wrf_check_error( WRFU_SUCCESS, rc, &
54                          'WRFU_TimeIntervalSet(zero_time) FAILED', &
55                          __FILE__ , &
56                          __LINE__  )
57    CALL WRFU_TimeIntervalSet ( one_minute, M=1, rc=rc )
58    CALL wrf_check_error( WRFU_SUCCESS, rc, &
59                          'WRFU_TimeIntervalSet(one_minute) FAILED', &
60                          __FILE__ , &
61                          __LINE__  )
62    CALL WRFU_TimeIntervalSet ( one_hour, H=1, rc=rc )
63    CALL wrf_check_error( WRFU_SUCCESS, rc, &
64                          'WRFU_TimeIntervalSet(one_hour) FAILED', &
65                          __FILE__ , &
66                          __LINE__  )
67    CALL WRFU_TimeIntervalSet ( forever, S=1700000000, rc=rc )  ! magic number; indicats an interval that is forever
68    CALL wrf_check_error( WRFU_SUCCESS, rc, &
69                          'WRFU_TimeIntervalSet(forever) FAILED', &
70                          __FILE__ , &
71                          __LINE__  )
73 ! #if (EM_CORE == 1)
74    IF ( (grid%dfi_opt .EQ. DFI_NODFI) .OR. (grid%dfi_stage .EQ. DFI_SETUP) ) THEN
75 ! #endif
76       CALL nl_get_start_year(grid%id,start_year)
77       CALL nl_get_start_month(grid%id,start_month)
78       CALL nl_get_start_day(grid%id,start_day)
79       CALL nl_get_start_hour(grid%id,start_hour)
80       CALL nl_get_start_minute(grid%id,start_minute)
81       CALL nl_get_start_second(grid%id,start_second)
82       CALL WRFU_TimeSet(startTime, YY=start_year, MM=start_month, DD=start_day, &
83                                    H=start_hour, M=start_minute, S=start_second,&
84                                    rc=rc)
85       CALL wrf_check_error( WRFU_SUCCESS, rc, &
86                             'WRFU_TimeSet(startTime) FAILED', &
87                             __FILE__ , &
88                             __LINE__  )
89 ! #if (EM_CORE == 1)
90    ELSE
91       IF ( grid%dfi_opt .EQ. DFI_DFL ) THEN
92          IF ( grid%dfi_stage .EQ. DFI_FWD ) THEN
93             CALL nl_get_start_year(grid%id,start_year)
94             CALL nl_get_start_month(grid%id,start_month)
95             CALL nl_get_start_day(grid%id,start_day)
96             CALL nl_get_start_hour(grid%id,start_hour)
97             CALL nl_get_start_minute(grid%id,start_minute)
98             CALL nl_get_start_second(grid%id,start_second)
99          ELSE IF ( grid%dfi_stage .EQ. DFI_FST ) THEN
100             CALL nl_get_start_year(grid%id,start_year)
101             CALL nl_get_start_month(grid%id,start_month)
102             CALL nl_get_start_day(grid%id,start_day)
103             CALL nl_get_start_hour(grid%id,start_hour)
104             CALL nl_get_start_minute(grid%id,start_minute)
105             CALL nl_get_start_second(grid%id,start_second)
107             run_length = grid%stop_subtime - grid%start_subtime
108             CALL WRFU_TimeIntervalGet( run_length, S=run_seconds, rc=rc )
109 ! What about fractional seconds?
110             run_seconds = run_seconds / 2
111             CALL WRFU_TimeIntervalSet ( run_length, S=run_seconds, rc=rc )
112             CALL WRFU_TimeSet(startTime, YY=start_year, MM=start_month, DD=start_day, &
113                                          H=start_hour, M=start_minute, S=start_second,&
114                                          rc=rc)
115             startTime = startTime + run_length
116             CALL WRFU_TimeGet(startTime, YY=start_year, MM=start_month, DD=start_day, &
117                                          H=start_hour, M=start_minute, S=start_second,&
118                                          rc=rc)
119          END IF
121       ELSE IF ( grid%dfi_opt .EQ. DFI_DDFI ) THEN
122          IF ( grid%dfi_stage .EQ. DFI_FWD ) THEN
123             CALL nl_get_dfi_bckstop_year(grid%id,start_year)
124             CALL nl_get_dfi_bckstop_month(grid%id,start_month)
125             CALL nl_get_dfi_bckstop_day(grid%id,start_day)
126             CALL nl_get_dfi_bckstop_hour(grid%id,start_hour)
127             CALL nl_get_dfi_bckstop_minute(grid%id,start_minute)
128             CALL nl_get_dfi_bckstop_second(grid%id,start_second)
129          ELSE IF ( grid%dfi_stage .EQ. DFI_BCK ) THEN
130             CALL nl_get_start_year(grid%id,start_year)
131             CALL nl_get_start_month(grid%id,start_month)
132             CALL nl_get_start_day(grid%id,start_day)
133             CALL nl_get_start_hour(grid%id,start_hour)
134             CALL nl_get_start_minute(grid%id,start_minute)
135             CALL nl_get_start_second(grid%id,start_second)
136          ELSE IF ( grid%dfi_stage .EQ. DFI_FST ) THEN
137             CALL nl_get_start_year(grid%id,start_year)
138             CALL nl_get_start_month(grid%id,start_month)
139             CALL nl_get_start_day(grid%id,start_day)
140             CALL nl_get_start_hour(grid%id,start_hour)
141             CALL nl_get_start_minute(grid%id,start_minute)
142             CALL nl_get_start_second(grid%id,start_second)
143          END IF
145       ELSE IF ( grid%dfi_opt .EQ. DFI_TDFI ) THEN
146          IF ( grid%dfi_stage .EQ. DFI_FWD ) THEN
147             CALL nl_get_dfi_bckstop_year(grid%id,start_year)
148             CALL nl_get_dfi_bckstop_month(grid%id,start_month)
149             CALL nl_get_dfi_bckstop_day(grid%id,start_day)
150             CALL nl_get_dfi_bckstop_hour(grid%id,start_hour)
151             CALL nl_get_dfi_bckstop_minute(grid%id,start_minute)
152             CALL nl_get_dfi_bckstop_second(grid%id,start_second)
154             ! Here, we look at head_grid to determine run_length.
155             !   Since start_subtime and stop_subtime were
156             !   updated for nesting, they no longer bound the dfi
157             !   time window, so, start_subtime and stop_subtime from
158             !   from the grid structure won't work.  However, we can use
159             !   head_grid since the dfi time window is the same for all 
160             !   domains.
162             run_length = head_grid%start_subtime - head_grid%stop_subtime
163             CALL WRFU_TimeIntervalGet( run_length, S=run_seconds, rc=rc )
164 ! What about fractional seconds?
165             run_seconds = run_seconds / 2
166             CALL WRFU_TimeIntervalSet ( run_length, S=run_seconds, rc=rc )
167             CALL WRFU_TimeSet(startTime, YY=start_year, MM=start_month, DD=start_day, &
168                                          H=start_hour, M=start_minute, S=start_second,&
169                                          rc=rc)
170             startTime = startTime + run_length
171             CALL WRFU_TimeGet(startTime, YY=start_year, MM=start_month, DD=start_day, &
172                                          H=start_hour, M=start_minute, S=start_second,&
173                                          rc=rc)
174          ELSE IF ( grid%dfi_stage .EQ. DFI_BCK ) THEN
175             CALL nl_get_start_year(grid%id,start_year)
176             CALL nl_get_start_month(grid%id,start_month)
177             CALL nl_get_start_day(grid%id,start_day)
178             CALL nl_get_start_hour(grid%id,start_hour)
179             CALL nl_get_start_minute(grid%id,start_minute)
180             CALL nl_get_start_second(grid%id,start_second)
181          ELSE IF ( grid%dfi_stage .EQ. DFI_FST ) THEN
182             CALL nl_get_start_year(grid%id,start_year)
183             CALL nl_get_start_month(grid%id,start_month)
184             CALL nl_get_start_day(grid%id,start_day)
185             CALL nl_get_start_hour(grid%id,start_hour)
186             CALL nl_get_start_minute(grid%id,start_minute)
187             CALL nl_get_start_second(grid%id,start_second)
188          ELSE IF ( grid%dfi_stage .EQ. DFI_STARTFWD ) THEN
189             CALL nl_get_start_year(grid%id,start_year)
190             CALL nl_get_start_month(grid%id,start_month)
191             CALL nl_get_start_day(grid%id,start_day)
192             CALL nl_get_start_hour(grid%id,start_hour)
193             CALL nl_get_start_minute(grid%id,start_minute)
194             CALL nl_get_start_second(grid%id,start_second)
195          END IF
196       END IF
198       IF ( grid%dfi_stage .EQ. DFI_STARTBCK ) THEN
199          CALL WRFU_ClockGet( grid%domain_clock, CurrTime=startTime, rc=rc)
200       ELSE
201          CALL WRFU_TimeSet(startTime, YY=start_year, MM=start_month, DD=start_day, &
202               H=start_hour, M=start_minute, S=start_second,&
203               rc=rc)
204       ENDIF
205       CALL wrf_check_error( WRFU_SUCCESS, rc, &
206                             'WRFU_TimeSet(startTime) FAILED', &
207                             __FILE__ , &
208                             __LINE__  )
209    END IF
210 ! #endif
212    CALL nl_get_run_days(1,run_days)
213    CALL nl_get_run_hours(1,run_hours)
214    CALL nl_get_run_minutes(1,run_minutes)
215    CALL nl_get_run_seconds(1,run_seconds)
217 ! #if (EM_CORE == 1)
218    IF ( (grid%dfi_opt .EQ. DFI_NODFI) .OR. (grid%dfi_stage .EQ. DFI_SETUP) .OR. (grid%dfi_stage .EQ. DFI_FST)) THEN
219 ! #endif
221       IF ( grid%id .EQ. head_grid%id .AND. &
222            ( run_days .gt. 0 .or. run_hours .gt. 0 .or. run_minutes .gt. 0 .or. run_seconds .gt. 0 )) THEN
223         CALL WRFU_TimeIntervalSet ( run_length , D=run_days, H=run_hours, M=run_minutes, S=run_seconds, rc=rc )
224 ! #if (EM_CORE == 1)
225         IF ( grid%dfi_stage .EQ. DFI_FST .AND. grid%dfi_opt .EQ. DFI_DFL ) THEN
226            CALL nl_get_start_year(grid%id,start_year)
227            CALL nl_get_start_month(grid%id,start_month)
228            CALL nl_get_start_day(grid%id,start_day)
229            CALL nl_get_start_hour(grid%id,start_hour)
230            CALL nl_get_start_minute(grid%id,start_minute)
231            CALL nl_get_start_second(grid%id,start_second)
232            CALL WRFU_TimeSet(initialTime, YY=start_year, MM=start_month, DD=start_day, &
233                                         H=start_hour, M=start_minute, S=start_second,&
234                                         rc=rc)
235            dfl_length = startTime - initialTime
236            run_length = run_length - dfl_length
237         END IF
238 ! #endif
239         CALL wrf_check_error( WRFU_SUCCESS, rc, &
240                            'WRFU_TimeIntervalSet(run_length) FAILED', &
241                            __FILE__ , &
242                            __LINE__  )
243         stopTime = startTime + run_length
244       ELSE
245         CALL nl_get_end_year(grid%id,end_year)
246         CALL nl_get_end_month(grid%id,end_month)
247         CALL nl_get_end_day(grid%id,end_day)
248         CALL nl_get_end_hour(grid%id,end_hour)
249         CALL nl_get_end_minute(grid%id,end_minute)
250         CALL nl_get_end_second(grid%id,end_second)
251         CALL WRFU_TimeSet(stopTime, YY=end_year, MM=end_month, DD=end_day, &
252                                  H=end_hour, M=end_minute, S=end_second,&
253                                  rc=rc )
254         CALL wrf_check_error( WRFU_SUCCESS, rc, &
255                            'WRFU_TimeSet(stopTime) FAILED', &
256                            __FILE__ , &
257                            __LINE__  )
258         run_length = stopTime - startTime
259       ENDIF
261 ! #if (EM_CORE == 1)
262    ELSE IF ( grid%dfi_stage .EQ. DFI_STARTFWD ) THEN
263       CALL nl_get_time_step ( 1, time_step )
264       CALL nl_get_time_step_fract_num( 1, time_step_fract_num )
265       CALL nl_get_time_step_fract_den( 1, time_step_fract_den )
266       CALL WRFU_TimeIntervalSet( run_length, S=time_step, Sn=time_step_fract_num, Sd=time_step_fract_den, rc=rc)
267       stopTime = startTime + run_length
268    ELSE IF ( grid%dfi_stage .EQ. DFI_STARTBCK ) THEN
269       CALL nl_get_time_step ( 1, time_step )
270       CALL nl_get_time_step_fract_num( 1, time_step_fract_num )
271       CALL nl_get_time_step_fract_den( 1, time_step_fract_den )
272       CALL WRFU_TimeIntervalSet( run_length, S=time_step, Sn=time_step_fract_num, Sd=time_step_fract_den, rc=rc)
273       stopTime = startTime + run_length
274    ELSE
275       IF ( grid%dfi_opt .EQ. DFI_DFL ) THEN 
276          IF ( grid%dfi_stage .EQ. DFI_FWD ) THEN
277             CALL nl_get_dfi_fwdstop_year(grid%id,end_year)
278             CALL nl_get_dfi_fwdstop_month(grid%id,end_month)
279             CALL nl_get_dfi_fwdstop_day(grid%id,end_day)
280             CALL nl_get_dfi_fwdstop_hour(grid%id,end_hour)
281             CALL nl_get_dfi_fwdstop_minute(grid%id,end_minute)
282             CALL nl_get_dfi_fwdstop_second(grid%id,end_second)
283          END IF
285       ELSE IF ( grid%dfi_opt .EQ. DFI_DDFI ) THEN 
286          IF ( grid%dfi_stage .EQ. DFI_FWD ) THEN
287             CALL nl_get_dfi_fwdstop_year(grid%id,end_year)
288             CALL nl_get_dfi_fwdstop_month(grid%id,end_month)
289             CALL nl_get_dfi_fwdstop_day(grid%id,end_day)
290             CALL nl_get_dfi_fwdstop_hour(grid%id,end_hour)
291             CALL nl_get_dfi_fwdstop_minute(grid%id,end_minute)
292             CALL nl_get_dfi_fwdstop_second(grid%id,end_second)
293          ELSE IF ( grid%dfi_stage .EQ. DFI_BCK ) THEN
294             CALL nl_get_dfi_bckstop_year(grid%id,end_year)
295             CALL nl_get_dfi_bckstop_month(grid%id,end_month)
296             CALL nl_get_dfi_bckstop_day(grid%id,end_day)
297             CALL nl_get_dfi_bckstop_hour(grid%id,end_hour)
298             CALL nl_get_dfi_bckstop_minute(grid%id,end_minute)
299             CALL nl_get_dfi_bckstop_second(grid%id,end_second)
300          END IF
302       ELSE IF ( grid%dfi_opt .EQ. DFI_TDFI ) THEN 
303          IF ( grid%dfi_stage .EQ. DFI_FWD ) THEN
304             CALL nl_get_dfi_fwdstop_year(grid%id,end_year)
305             CALL nl_get_dfi_fwdstop_month(grid%id,end_month)
306             CALL nl_get_dfi_fwdstop_day(grid%id,end_day)
307             CALL nl_get_dfi_fwdstop_hour(grid%id,end_hour)
308             CALL nl_get_dfi_fwdstop_minute(grid%id,end_minute)
309             CALL nl_get_dfi_fwdstop_second(grid%id,end_second)
310          ELSE IF ( grid%dfi_stage .EQ. DFI_BCK ) THEN
311             CALL nl_get_dfi_bckstop_year(grid%id,end_year)
312             CALL nl_get_dfi_bckstop_month(grid%id,end_month)
313             CALL nl_get_dfi_bckstop_day(grid%id,end_day)
314             CALL nl_get_dfi_bckstop_hour(grid%id,end_hour)
315             CALL nl_get_dfi_bckstop_minute(grid%id,end_minute)
316             CALL nl_get_dfi_bckstop_second(grid%id,end_second)
317          END IF
318       END IF
319       CALL WRFU_TimeSet(stopTime, YY=end_year, MM=end_month, DD=end_day, &
320                          H=end_hour, M=end_minute, S=end_second,&
321                                 rc=rc)
323       CALL wrf_check_error( WRFU_SUCCESS, rc, &
324                    'WRFU_TimeSet(dfistopfwdTime) FAILED', &
325                    __FILE__ , &
326                    __LINE__  )
328       run_length = stopTime - startTime
330    END IF
331 ! #endif
333    IF ( run_length .GT. zero_time ) THEN
334      padding_interval = forever
335    ELSE
336      padding_interval = zero_time - forever
337    ENDIF
339    IF ( grid%id .EQ. head_grid%id ) THEN
340       CALL nl_get_time_step ( 1, time_step )
341       CALL nl_get_time_step_fract_num( 1, time_step_fract_num )
342       CALL nl_get_time_step_fract_den( 1, time_step_fract_den )
343       dt = real(time_step) + real(time_step_fract_num) / real(time_step_fract_den)
344 #ifdef PLANET
345       ! 2004-12-08 ADT notes:
346       ! We have gotten the timestep from integers in the namelist, and they have just
347       ! been converted to the timestep, "dt", used by the physics code just above.
348       ! After this point, the integers are only used to update the clock used for,
349       ! and we want to leave that on a "24-hour" type schedule, so we don't need to
350       ! modify those integers.  Theoretically they refer to a portion of the planet's
351       ! solar day.  The only thing we have to do is convert the *real* timestep, dt,
352       ! to useful SI units.  This is easily accomplished by multiplying it by the
353       ! variable P2SI, which was designed for just this purpose.  After multiplication,
354       ! make sure every subsequent part of the model knows what the value is.
355       dt = dt * P2SI
356 #endif
357       CALL nl_set_dt( grid%id, dt )
358       grid%dt = dt
359       CALL WRFU_TimeIntervalSet(stepTime, S=time_step, Sn=time_step_fract_num, Sd=time_step_fract_den, rc=rc)
360       CALL wrf_check_error( WRFU_SUCCESS, rc, &
361                             'WRFU_TimeIntervalSet(stepTime) FAILED', &
362                             __FILE__ , &
363                             __LINE__  )
364    ELSE
365       tmp_step = domain_get_time_step( grid%parents(1)%ptr )
366       stepTime = domain_get_time_step( grid%parents(1)%ptr ) / &
367            grid%parent_time_step_ratio
368       grid%dt = grid%parents(1)%ptr%dt / grid%parent_time_step_ratio
369       CALL nl_set_dt( grid%id, grid%dt )
370    ENDIF
372    ! create grid%domain_clock and associated state
373    CALL domain_clock_create( grid, TimeStep= stepTime,  &
374                                    StartTime=startTime, &
375                                    StopTime= stopTime )
376    CALL domain_clockprint ( 150, grid, &
377           'DEBUG setup_timekeeping():  clock after creation,' )
379    ! Set default value for SIMULATION_START_DATE.  
380    ! This is overwritten later in input_wrf(), if needed.  
381    IF ( grid%id .EQ. head_grid%id ) THEN
382       CALL nl_set_simulation_start_year   ( 1 , start_year   )
383       CALL nl_set_simulation_start_month  ( 1 , start_month  )
384       CALL nl_set_simulation_start_day    ( 1 , start_day    )
385       CALL nl_set_simulation_start_hour   ( 1 , start_hour   )
386       CALL nl_set_simulation_start_minute ( 1 , start_minute )
387       CALL nl_set_simulation_start_second ( 1 , start_second )
388    ENDIF
390 #include "set_timekeeping_alarms.inc"
392 ! RESTART INTERVAL
393 ! restart_interval is left there (and means minutes) for consistency, but
394 ! restart_interval_m will take precedence if specified
395    CALL nl_get_restart_interval( 1, restart_interval )   ! same as minutes
396    CALL nl_get_restart_interval_d( 1, restart_interval_d )
397    CALL nl_get_restart_interval_h( 1, restart_interval_h )
398    CALL nl_get_restart_interval_m( 1, restart_interval_m )
399    CALL nl_get_restart_interval_s( 1, restart_interval_s )
400    IF ( restart_interval_m .EQ. 0 ) restart_interval_m = restart_interval
401    IF ( MAX( restart_interval_d,   &
402              restart_interval_h, restart_interval_m , restart_interval_s   ) .GT. 0 ) THEN
403      CALL WRFU_TimeIntervalSet( interval, D=restart_interval_d, &
404                                         H=restart_interval_h, M=restart_interval_m, S=restart_interval_s, rc=rc )
405      CALL wrf_check_error( WRFU_SUCCESS, rc, &
406                            'WRFU_TimeIntervalSet(restart_interval) FAILED', &
407                            __FILE__ , &
408                            __LINE__  )
409    ELSE
410      interval =  padding_interval
411    ENDIF
412    CALL domain_alarm_create( grid, RESTART_ALARM, interval )
414 ! INPUTOUT INTERVAL
415    CALL nl_get_inputout_interval( grid%id, inputout_interval )   ! same as minutes
416    CALL nl_get_inputout_interval_d( grid%id, inputout_interval_d )
417    CALL nl_get_inputout_interval_h( grid%id, inputout_interval_h )
418    CALL nl_get_inputout_interval_m( grid%id, inputout_interval_m )
419    CALL nl_get_inputout_interval_s( grid%id, inputout_interval_s )
420    IF ( inputout_interval_m .EQ. 0 ) inputout_interval_m = inputout_interval
422    IF ( MAX( inputout_interval_d,   &
423              inputout_interval_h, inputout_interval_m , inputout_interval_s   ) .GT. 0 ) THEN
424      CALL WRFU_TimeIntervalSet( interval, D=inputout_interval_d, &
425                                         H=inputout_interval_h, M=inputout_interval_m, S=inputout_interval_s, rc=rc )
426      CALL wrf_check_error( WRFU_SUCCESS, rc, &
427                            'WRFU_TimeIntervalSet(inputout_interval) FAILED', &
428                            __FILE__ , &
429                            __LINE__  )
430    ELSE
431      interval =  padding_interval
432    ENDIF
434    CALL nl_get_inputout_begin_y( grid%id, inputout_begin_y )
435    CALL nl_get_inputout_begin_d( grid%id, inputout_begin_d )
436    CALL nl_get_inputout_begin_h( grid%id, inputout_begin_h )
437    CALL nl_get_inputout_begin_m( grid%id, inputout_begin_m )
438    CALL nl_get_inputout_begin_s( grid%id, inputout_begin_s )
439    IF ( MAX( inputout_begin_y, inputout_begin_d,   &
440              inputout_begin_h, inputout_begin_m , inputout_begin_s   ) .GT. 0 ) THEN
441       CALL WRFU_TimeIntervalSet( begin_time , D=inputout_begin_d, &
442                                       H=inputout_begin_h, M=inputout_begin_m, S=inputout_begin_s, rc=rc )
443       CALL wrf_check_error( WRFU_SUCCESS, rc, &
444                             'WRFU_TimeIntervalSet(inputout_begin) FAILED', &
445                             __FILE__ , &
446                             __LINE__  )
447    ELSE
448       begin_time = zero_time
449    ENDIF
451    CALL nl_get_inputout_end_y( grid%id, inputout_end_y )
452    CALL nl_get_inputout_end_d( grid%id, inputout_end_d )
453    CALL nl_get_inputout_end_h( grid%id, inputout_end_h )
454    CALL nl_get_inputout_end_m( grid%id, inputout_end_m )
455    CALL nl_get_inputout_end_s( grid%id, inputout_end_s )
456    IF ( MAX( inputout_end_y, inputout_end_d,   &
457              inputout_end_h, inputout_end_m , inputout_end_s   ) .GT. 0 ) THEN
458       CALL WRFU_TimeIntervalSet( end_time , D=inputout_end_d, &
459                                      H=inputout_end_h, M=inputout_end_m, S=inputout_end_s, rc=rc )
460       CALL wrf_check_error( WRFU_SUCCESS, rc, &
461                             'WRFU_TimeIntervalSet(inputout_end) FAILED', &
462                             __FILE__ , &
463                             __LINE__  )
464    ELSE
465       end_time =  padding_interval
466    ENDIF
468    CALL domain_alarm_create( grid, INPUTOUT_ALARM, interval, begin_time, end_time )
470 #if ( WRF_CHEM == 1 )
471 ! AUXINPUT5_ INTERVAL
472 ! auxinput5_interval is left there (and means minutes) for consistency, but
473 ! auxinput5_interval_m will take precedence if specified
474    CALL nl_get_auxinput5_interval( grid%id, auxinput5_interval )   ! same as minutes
475    CALL nl_get_auxinput5_interval_d( grid%id, auxinput5_interval_d )
476    CALL nl_get_auxinput5_interval_h( grid%id, auxinput5_interval_h )
477    CALL nl_get_auxinput5_interval_m( grid%id, auxinput5_interval_m )
478    CALL nl_get_auxinput5_interval_s( grid%id, auxinput5_interval_s )
479    IF ( auxinput5_interval_m .EQ. 0 ) auxinput5_interval_m = auxinput5_interval
481    IF ( MAX( auxinput5_interval_d,   &
482              auxinput5_interval_h, auxinput5_interval_m , auxinput5_interval_s   ) .GT. 0 ) THEN
483      CALL WRFU_TimeIntervalSet( interval, D=auxinput5_interval_d, &
484                                         H=auxinput5_interval_h, M=auxinput5_interval_m, S=auxinput5_interval_s, rc=rc )
485      CALL wrf_check_error( WRFU_SUCCESS, rc, &
486                            'WRFU_TimeIntervalSet(auxinput5_interval) FAILED', &
487                            __FILE__ , &
488                            __LINE__  )
489    ELSE
490      interval =  padding_interval
491    ENDIF
493    CALL nl_get_auxinput5_begin_y( grid%id, auxinput5_begin_y )
494    CALL nl_get_auxinput5_begin_d( grid%id, auxinput5_begin_d )
495    CALL nl_get_auxinput5_begin_h( grid%id, auxinput5_begin_h )
496    CALL nl_get_auxinput5_begin_m( grid%id, auxinput5_begin_m )
497    CALL nl_get_auxinput5_begin_s( grid%id, auxinput5_begin_s )
498    IF ( MAX( auxinput5_begin_y, auxinput5_begin_d,   &
499              auxinput5_begin_h, auxinput5_begin_m , auxinput5_begin_s   ) .GT. 0 ) THEN
500       CALL WRFU_TimeIntervalSet( begin_time , D=auxinput5_begin_d, &
501                                       H=auxinput5_begin_h, M=auxinput5_begin_m, S=auxinput5_begin_s, rc=rc )
502       CALL wrf_check_error( WRFU_SUCCESS, rc, &
503                             'WRFU_TimeIntervalSet(auxinput5_begin) FAILED', &
504                             __FILE__ , &
505                             __LINE__  )
506    ELSE
507       begin_time = zero_time
508    ENDIF
509    CALL nl_get_auxinput5_end_y( grid%id, auxinput5_end_y )
510    CALL nl_get_auxinput5_end_d( grid%id, auxinput5_end_d )
511    CALL nl_get_auxinput5_end_h( grid%id, auxinput5_end_h )
512    CALL nl_get_auxinput5_end_m( grid%id, auxinput5_end_m )
513    CALL nl_get_auxinput5_end_s( grid%id, auxinput5_end_s )
514    IF ( MAX( auxinput5_end_y, auxinput5_end_d,   &
515              auxinput5_end_h, auxinput5_end_m , auxinput5_end_s   ) .GT. 0 ) THEN
516       CALL WRFU_TimeIntervalSet( end_time , D=auxinput5_end_d, &
517                                      H=auxinput5_end_h, M=auxinput5_end_m, S=auxinput5_end_s, rc=rc )
518       CALL wrf_check_error( WRFU_SUCCESS, rc, &
519                             'WRFU_TimeIntervalSet(auxinput5_end) FAILED', &
520                             __FILE__ , &
521                             __LINE__  )
522    ELSE
523       end_time =  padding_interval
524    ENDIF
525    CALL domain_alarm_create( grid, AUXINPUT5_ALARM, interval, begin_time, end_time )
526 !TBH:  Should be OK to remove the "#else" section and the code it contains 
527 !TBH:  because later code overwrites grid%alarms( AUXINPUT5_ALARM )...  
528 !TBH:  In fact, by setting namelist values for auxinput5 correctly, it ought 
529 !TBH:  to be possible to get rid of all "#if ( WRF_CHEM == 1 )" bits in this file...  
530    CALL WRFU_AlarmEnable( grid%alarms( AUXINPUT5_ALARM ), rc=rc )
531    CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT5_ALARM ), rc=rc )
532 ! TBH:  NOTE:  Proper setting of namelist variables for auxinput5 ought to 
533 ! TBH:         make this hard-coded bit unnecessary.  
534 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
535 ! add for wrf_chem emiss input
536    CALL WRFU_AlarmEnable( grid%alarms( AUXINPUT5_ALARM ), rc=rc )
537    CALL WRFU_AlarmRingerOn( grid%alarms( AUXINPUT5_ALARM ), rc=rc )
538 ! end for wrf chem emiss input
539 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
540 #endif
542 ! without this test, it's possible for the value of the WRF_ALARM_SECS_TIL_NEXT_RING
543 ! that is written as metadata to a restart file to be garbage for BOUNDARY_ALARM for 
544 ! the nests.  Parallel NetCDF does a header check on all the metadata being written
545 ! from multiple processors and if it differs, it throws up an error. This avoids that.
546    IF ( grid%id .EQ. 1 ) THEN   ! only moad can have specified boundaries
547      CALL domain_alarm_create( grid, BOUNDARY_ALARM, interval )
548      CALL WRFU_AlarmEnable( grid%alarms( BOUNDARY_ALARM ), rc=rc )
549      CALL wrf_check_error( WRFU_SUCCESS, rc, &
550                            'WRFU_AlarmEnable(BOUNDARY_ALARM) FAILED', &
551                            __FILE__ , &
552                            __LINE__  )
553      CALL WRFU_AlarmRingerOn( grid%alarms( BOUNDARY_ALARM ), rc=rc )
554      CALL wrf_check_error( WRFU_SUCCESS, rc, &
555                            'WRFU_AlarmRingerOn(BOUNDARY_ALARM) FAILED', &
556                            __FILE__ , &
557                            __LINE__  )
558    ENDIF
560 ! This is the interval at which the code in time_for_move in share/mediation_integrate.F
561 ! will recompute the center of the Vortex.  Other times, it will use the last position.
563    vortex_interval = 0
564 #ifdef MOVE_NESTS
565    CALL nl_get_vortex_interval ( grid%id , vortex_interval ) 
566 #endif
567    CALL WRFU_TimeIntervalSet( interval, M=vortex_interval, rc=rc )
568    CALL wrf_check_error( WRFU_SUCCESS, rc, &
569                            'WRFU_TimeIntervalSet(interval) for computing vortex center FAILED', &
570                            __FILE__ , &
571                            __LINE__  )
572    CALL domain_alarm_create( grid,  COMPUTE_VORTEX_CENTER_ALARM, interval  )
573 #ifdef MOVE_NESTS
574    CALL WRFU_AlarmEnable( grid%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
575    CALL wrf_check_error( WRFU_SUCCESS, rc, &
576                          'WRFU_AlarmEnable(COMPUTE_VORTEX_CENTER_ALARM) FAILED', &
577                          __FILE__ , &
578                          __LINE__  )
579    CALL WRFU_AlarmRingerOn( grid%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
580    CALL wrf_check_error( WRFU_SUCCESS, rc, &
581                          'WRFU_AlarmRingerOn(COMPUTE_VORTEX_CENTER_ALARM) FAILED', &
582                          __FILE__ , &
583                          __LINE__  )
584 #else
585 ! Go ahead and let the alarm be defined, but disable it, since we are not using moving nests here.
586    CALL WRFU_AlarmDisable( grid%alarms( COMPUTE_VORTEX_CENTER_ALARM ), rc=rc )
587    CALL wrf_check_error( WRFU_SUCCESS, rc, &
588                          'WRFU_AlarmDisable(COMPUTE_VORTEX_CENTER_ALARM) FAILED', &
589                          __FILE__ , &
590                          __LINE__  )
591 #endif
593    grid%time_set = .TRUE.
595    ! Initialize derived time quantities in grid state.  
596    ! These are updated in domain_clockadvance().  
597    CALL domain_clock_get( grid, minutesSinceSimulationStart=grid%xtime )
598    CALL domain_clock_get( grid, currentDayOfYearReal=grid%julian )
599    WRITE(wrf_err_message,*) 'setup_timekeeping:  set xtime to ',grid%xtime
600    CALL wrf_debug ( 100, TRIM(wrf_err_message) )
601    WRITE(wrf_err_message,*) 'setup_timekeeping:  set julian to ',grid%julian
602    CALL wrf_debug ( 100, TRIM(wrf_err_message) )
604    CALL wrf_debug ( 100 , 'setup_timekeeping:  returning...' )
606 END SUBROUTINE Setup_Timekeeping