module_integrate_tst.F

References to this file elsewhere.
1 !WRF:DRIVER_LAYER:INTEGRATION
2 !
3 
4 MODULE module_integrate_tst
5 
6 CONTAINS
7 
8 RECURSIVE SUBROUTINE integrate_tst ( grid )
9 
10 
11 
12    USE module_domain
13    USE module_driver_constants
14    USE module_nesting
15    USE module_configure
16    USE module_timing
17    USE esmf_mod
18 
19    IMPLICIT NONE
20 
21    !  Input data.
22 
23    TYPE(domain) , POINTER :: grid
24 
25 ! module_integrate:integrate
26 ! <DESCRIPTION> 
27 ! This is a driver-level routine that controls the integration of a
28 ! domain and subdomains rooted at the domain. 
29 ! 
30 ! The integrate routine takes a domain pointed to by the argument
31 ! <em>grid</em> and advances the domain and its associated nests from the
32 ! grid's current time, stored as grid%current_time, to a given time
33 ! forward in the simulation, stored as grid%stop_subtime. The
34 ! stop_subtime value is arbitrary and does not have to be the same as
35 ! time that the domain finished integrating.  The simulation stop time
36 ! for the grid is known to the grid's clock (grid%domain_clock) and that
37 ! is checked with a call to ESMF_ClockIsStopTime prior to beginning the
38 ! loop over time period that is specified by the
39 ! current_time/stop_subtime interval.
40 ! 
41 ! The clock, the simulation stop time for the domain, and other timing
42 ! aspects for the grid are set up in the routine
43 ! (<a href="setup_timekeeping.html">setup_timekeeping</a>) at the time
44 ! that the domain is initialized.
45 ! The lower-level time library and the type declarations for the times
46 ! and time intervals used are defined in external/esmf_time_f90.
47 !  Note that arithmetic and comparison is performed 
48 ! on these data types using F90 operator overloading, also defined in that 
49 ! library.
50 ! 
51 ! This routine is the lowest level of the WRF Driver Layer and for the most
52 ! part the WRF routines that are called from here are in the topmost level
53 ! of the Mediation Layer.  Mediation layer routines typically are not 
54 ! defined in modules. Therefore, the routines that this routine calls
55 ! have explicit interfaces specified in an interface block in this routine.
56 !
57 ! As part of the Driver Layer, this routine is intended to be non model-specific
58 ! and so a minimum of WRF-specific logic is coded at this level. Rather, there
59 ! are a number of calls to mediation layer routines that contain this logic, some
60 ! of which are merely stubs in WRF Mediation Layer that sits below this routine
61 ! in the call tree.  The routines that integrate calls in WRF are defined in
62 ! share/mediation_integrate.F.
63 ! 
64 ! Flow of control
65 ! 
66 ! 1. Check to see that the domain is not finished 
67 ! by testing the value returned by ESMF_ClockIsStopTime for the
68 ! domain.
69 ! 
70 ! 2. <a href=model_to_grid_config_rec.html>Model_to_grid_config_rec</a> is called to load the local config_flags
71 ! structure with the configuration information for the grid stored
72 ! in model_config_rec and indexed by the grid's unique integer id. These
73 ! structures are defined in frame/module_configure.F.
74 ! 
75 ! 3. The current time of the domain is retrieved from the domain's clock
76 ! using ESMF_ClockGet.  There is another call to ESMF_ClockGet
77 ! inside the WHILE loop that follows.
78 ! 
79 ! 4. Iterate forward while the current time is less than the stop subtime.
80 ! 
81 ! 4.a. Start timing for this iteration (only on node zero in distributed-memory runs)
82 ! 
83 ! 4.b. Call <a href=med_setup_step.html>med_setup_step</a> to allow the mediation layer to 
84 ! do anything that's needed to call the solver for this domain.  In WRF this means setting
85 ! the indices into the 4D tracer arrays for the domain.
86 ! 
87 ! 4.c. Check for any nests that need to be started up at this time.  This is done 
88 ! calling the logical function <a href=nests_to_open.html>nests_to_open</a> (defined in 
89 ! frame/module_nesting.F) which returns true and the index into the current domain's list
90 ! of children to use for the nest when one needs to be started.
91 ! 
92 ! 4.c.1  Call <a href=alloc_and_configure_domain.html>alloc_and_configure_domain</a> to allocate
93 ! the new nest and link it as a child of this grid.
94 ! 
95 ! 4.c.2  Call <a href=setup_Timekeeping.html>setup_Timekeeping</a> for the nest.
96 ! 
97 ! 4.c.3  Initialize the nest's arrays by calling <a href=med_nest_initial.html>med_nest_initial</a>. This will
98 ! either interpolate data from this grid onto the nest, read it in from a file, or both. In a restart run, this
99 ! is also where the nest reads in its restart file.
100 ! 
101 ! 4.d  If a nest was opened above, check for and resolve overlaps (this is not implemented in WRF 2.0, which
102 ! supports multiple nests on the same level but does not support overlapping).
103 ! 
104 ! 4.e  Give the mediation layer an opportunity to do something before the solver is called by
105 ! calling <a href=med_before_solve_io.html>med_before_solve_io</a>. In WRF this is the point at which history and
106 ! restart data is output.
107 ! 
108 ! 4.f  Call <a href=solve_interface_tst.html>solve_interface_tst</a> which calls the solver that advance the domain 
109 ! one time step, then advance the domain's clock by calling ESMF_ClockAdvance.  Upon advancing the clock,
110 ! the current time for the grid is updated by calling ESMF_ClockGet. The enclosing WHILE loop around
111 ! this section is for handling other domains with which this domain may overlap.  It is not active in WRF 2.0 and
112 ! only executes one trip.  
113 ! 
114 ! 4.g Call med_calc_model_time and med_after_solve_io, which are stubs in WRF.
115 ! 
116 ! 4.h Iterate over the children of this domain (<tt>DO kid = 1, max_nests</tt>) and check each child pointer to see
117 ! if it is associated (and therefore, active).
118 ! 
119 ! 4.h.1  Force the nested domain boundaries from this domain by calling <a href=med_nest_force.html>med_nest_force</a>.
120 ! 
121 ! 4.h.2  Setup the time period over which the nest is to run. Sine the current grid has been advanced one time step
122 ! and the nest has not, the start for the nest is this grid's current time minus one time step.  The nest's stop_subtime
123 ! is the current time, bringing the nest up the same time level as this grid, its parent.
124 ! 
125 ! 4.h.3  Recursively call this routine, integrate, to advance the nest's time.  Since it is recursive, this will
126 ! also advance all the domains who are nests of this nest and so on.  In other words, when this call returns, all
127 ! the domains rooted at the nest will be at the current time.
128 ! 
129 ! 4.h.4  Feedback data from the nested domain back onto this domain by calling <a href=med_nest_feedback.html>med_nest_feedback</a>.
130 ! 
131 ! 4.i  Write the time to compute this grid and its subtree. This marks the end of the loop begun at step 4, above.
132 ! 
133 ! 5. Give the mediation layer an opportunity to do I/O at the end of the sequence of steps that brought the
134 ! grid up to stop_subtime with a call to <a href=med_last_solve_io.html>med_last_solve_io</a>.  In WRF, this 
135 ! is used to generate the final history and/or restart output when the domain reaches the end of it's integration.
136 ! There is logic here to make sure this occurs correctly on a nest, since the nest may finish before its parent.
137 ! </DESCRIPTION>
138 
139    !  Local data.
140 
141    CHARACTER*32                           :: outname, rstname
142    TYPE(domain) , POINTER                 :: grid_ptr , new_nest
143    TYPE(domain)                           :: intermediate_grid
144    INTEGER                                :: step
145    INTEGER                                :: nestid , kid
146    LOGICAL                                :: a_nest_was_opened
147    INTEGER                                :: fid , rid
148    LOGICAL                                :: lbc_opened
149    REAL                                   :: time, btime, bfrq
150    CHARACTER*256                          :: message, message2
151    TYPE (grid_config_rec_type)            :: config_flags
152    LOGICAL , EXTERNAL                     :: wrf_dm_on_monitor
153    INTEGER                                :: idum1 , idum2 , ierr , open_status
154    INTEGER                                :: rc
155 
156    ! interface
157    INTERFACE
158        ! mediation-supplied solver
159      SUBROUTINE solve_interface_tst ( grid )
160        USE module_domain
161        TYPE (domain) grid
162      END SUBROUTINE solve_interface_tst
163        ! mediation-supplied routine to allow driver to pass time information
164        ! down to mediation/model layer
165      SUBROUTINE med_calc_model_time ( grid , config_flags )
166        USE module_domain
167        USE module_configure
168        TYPE (domain) grid
169        TYPE (grid_config_rec_type) config_flags
170      END SUBROUTINE med_calc_model_time
171        ! mediation-supplied routine that gives mediation layer opportunity to 
172        ! perform I/O before the call to the solve routine
173      SUBROUTINE med_before_solve_io ( grid , config_flags )
174        USE module_domain
175        USE module_configure
176        TYPE (domain) grid
177        TYPE (grid_config_rec_type) config_flags
178      END SUBROUTINE med_before_solve_io
179        ! mediation-supplied routine that gives mediation layer opportunity to 
180        ! perform I/O after the call to the solve routine
181      SUBROUTINE med_after_solve_io ( grid , config_flags )
182        USE module_domain
183        USE module_configure
184        TYPE (domain) grid
185        TYPE (grid_config_rec_type) config_flags
186      END SUBROUTINE med_after_solve_io
187        ! mediation-supplied routine that gives mediation layer opportunity to 
188        ! perform I/O to initialize a new nest
189      SUBROUTINE med_nest_initial ( parent , grid , config_flags )
190        USE module_domain
191        USE module_configure
192        TYPE (domain), POINTER ::  grid , parent
193        TYPE (grid_config_rec_type) config_flags
194      END SUBROUTINE med_nest_initial
195 
196        ! mediation-supplied routine that gives mediation layer opportunity to 
197        ! provide parent->nest forcing
198      SUBROUTINE med_nest_force ( parent , grid , config_flags )
199        USE module_domain
200        USE module_configure
201        TYPE (domain), POINTER ::  grid , parent
202        TYPE (grid_config_rec_type) config_flags
203      END SUBROUTINE med_nest_force
204 
205 #ifdef MOVE_NESTS
206      SUBROUTINE med_nest_move ( parent , grid )
207        USE module_domain
208        USE module_configure
209        TYPE (domain), POINTER ::  grid , parent
210      END SUBROUTINE med_nest_move
211 #endif
212 
213        ! mediation-supplied routine that gives mediation layer opportunity to 
214        ! provide parent->nest feedback
215      SUBROUTINE med_nest_feedback ( parent , grid , config_flags )
216        USE module_domain
217        USE module_configure
218        TYPE (domain), POINTER ::  grid , parent
219        TYPE (grid_config_rec_type) config_flags
220      END SUBROUTINE med_nest_feedback
221 
222        ! mediation-supplied routine that gives mediation layer opportunity to 
223        ! perform I/O prior to the close of this call to integrate
224      SUBROUTINE med_last_solve_io ( grid , config_flags )
225        USE module_domain
226        USE module_configure
227        TYPE (domain) grid
228        TYPE (grid_config_rec_type) config_flags
229      END SUBROUTINE med_last_solve_io
230        ! mediation-supplied routine that gives mediation layer opportunity to 
231        ! perform setup before iteration over steps in this call to integrate
232      SUBROUTINE med_setup_step ( grid , config_flags )
233        USE module_domain
234        USE module_configure
235        TYPE (domain) grid
236        TYPE (grid_config_rec_type) config_flags
237      END SUBROUTINE med_setup_step
238        ! mediation-supplied routine that intializes the nest from the grid
239        ! by interpolation
240 
241      SUBROUTINE Setup_Timekeeping( grid )
242        USE module_domain
243        TYPE(domain), POINTER :: grid
244      END SUBROUTINE
245 
246    END INTERFACE
247 
248    IF ( .NOT. ESMF_ClockIsStopTime(grid%domain_clock ,rc=rc) ) THEN
249       CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
250       CALL wrf_clockprint ( 150, grid%domain_clock, &
251                             'DEBUG:  top of integrate(),' )
252       DO WHILE ( domain_get_current_time(grid) .LT. grid%stop_subtime )
253          IF ( wrf_dm_on_monitor() ) THEN
254            CALL start_timing
255          END IF
256          CALL med_setup_step ( grid , config_flags )
257          a_nest_was_opened = .false.
258          ! for each nest whose time has come...
259          DO WHILE ( nests_to_open( grid , nestid , kid ) )
260             ! nestid is index into model_config_rec (module_configure) of the grid
261             ! to be opened; kid is index into an open slot in grid's list of children
262             a_nest_was_opened = .true.
263             CALL alloc_and_configure_domain ( domain_id  = nestid ,                          &
264                                               grid       = new_nest ,                        &
265                                               parent     = grid ,                            &
266                                               kid        = kid                               )
267             CALL Setup_Timekeeping (new_nest)
268             CALL med_nest_initial ( grid , new_nest , config_flags )
269          END DO
270          IF ( a_nest_was_opened ) THEN
271             CALL set_overlaps ( grid )   ! find overlapping and set pointers
272          END IF
273          CALL med_before_solve_io ( grid , config_flags )
274          grid_ptr => grid
275          DO WHILE ( ASSOCIATED( grid_ptr ) )
276             CALL wrf_debug( 100 , 'module_integrate: calling solve interface ' )
277             CALL solve_interface_tst ( grid_ptr ) 
278             CALL wrf_clockprint ( 150, grid_ptr%domain_clock, &
279                                   'DEBUG integrate():  before ESMF_ClockAdvance,' )
280             CALL ESMF_ClockAdvance( grid_ptr%domain_clock, rc=rc )
281             CALL wrf_check_error( ESMF_SUCCESS, rc, &
282                                   'ESMF_ClockAdvance() FAILED', &
283                                   __FILE__ , &
284                                   __LINE__  )
285             CALL wrf_clockprint ( 150, grid_ptr%domain_clock, &
286                                   'DEBUG integrate():  after ESMF_ClockAdvance,' )
287             CALL wrf_debug( 100 , 'module_integrate: back from solve interface ' )
288             grid_ptr => grid_ptr%sibling
289          END DO
290          CALL med_calc_model_time ( grid , config_flags )
291          CALL med_after_solve_io ( grid , config_flags )
292          grid_ptr => grid
293          DO WHILE ( ASSOCIATED( grid_ptr ) )
294             DO kid = 1, max_nests
295               IF ( ASSOCIATED( grid_ptr%nests(kid)%ptr ) ) THEN
296                 ! Recursive -- advance nests from previous time level to this time level.
297                 CALL wrf_debug( 100 , 'module_integrate: calling med_nest_force ' )
298                 CALL med_nest_force ( grid_ptr , grid_ptr%nests(kid)%ptr , config_flags )
299                 CALL wrf_debug( 100 , 'module_integrate: back from med_nest_force ' )
300                 grid_ptr%nests(kid)%ptr%start_subtime = &
301                   domain_get_current_time(grid) - domain_get_time_step(grid)
302                 grid_ptr%nests(kid)%ptr%stop_subtime = &
303                   domain_get_current_time(grid)
304                 CALL integrate_tst ( grid_ptr%nests(kid)%ptr ) 
305                 CALL wrf_debug( 100 , 'module_integrate: back from recursive call to integrate ' )
306                 CALL wrf_debug( 100 , 'module_integrate: calling med_nest_feedback ' )
307                 CALL med_nest_feedback ( grid_ptr , grid_ptr%nests(kid)%ptr , config_flags )
308                 CALL wrf_debug( 100 , 'module_integrate: back from med_nest_feedback ' )
309 #ifdef MOVE_NESTS
310                 CALL med_nest_move ( grid_ptr , grid_ptr%nests(kid)%ptr )
311 #endif
312               END IF
313             END DO
314             grid_ptr => grid_ptr%sibling
315          END DO
316          !  Report on the timing for a single time step.
317          IF ( wrf_dm_on_monitor() ) THEN
318            CALL wrf_timetoa ( domain_get_current_time(grid), message2 )
319            WRITE ( message , FMT = '("main: time ",A," on domain ",I3)' ) TRIM(message2), grid%id
320            CALL end_timing ( TRIM(message) )
321          END IF
322       END DO
323       ! Avoid double writes on nests if this is not really the last time;
324       ! Do check for write if the parent domain is ending.
325       IF ( grid%id .EQ. 1 ) THEN               ! head_grid
326         CALL med_last_solve_io ( grid , config_flags )
327       ELSE
328         IF ( ESMF_ClockIsStopTime(grid%domain_clock , rc=rc) .OR. &
329              ESMF_ClockIsStopTime(grid%parents(1)%ptr%domain_clock , rc=rc ) ) THEN
330            CALL med_last_solve_io ( grid , config_flags )
331         ENDIF
332       ENDIF
333    END IF
334 
335 END SUBROUTINE integrate_tst
336 
337 END MODULE module_integrate_tst