module_configure.F

References to this file elsewhere.
1 !WRF:DRIVER_LAYER:CONFIGURATION
2 !
3 MODULE module_configure
4 
5    USE module_driver_constants
6    USE module_state_description
7    USE module_wrf_error
8 
9    TYPE model_config_rec_type
10       SEQUENCE
11 ! Statements that declare namelist variables are in this file
12 ! Note that the namelist is SEQUENCE and generated such that the first item is an
13 ! integer, first_item_in_struct and the last is an integer last_item_in_struct
14 ! this provides a way of converting this to a buffer for passing to and from
15 ! the driver.
16 #include <namelist_defines.inc>
17    END TYPE model_config_rec_type
18 
19    TYPE grid_config_rec_type
20 #include <namelist_defines2.inc>
21    END TYPE grid_config_rec_type
22 
23    TYPE(model_config_rec_type) :: model_config_rec
24 
25 #include <scalar_tables.inc>
26 
27 ! special entries (put here but not enshrined in Registry for one reason or other)
28 
29    CHARACTER (LEN=4) :: mminlu = '    '         ! character string for landuse table
30 
31 CONTAINS
32 
33 
34 ! Model layer, even though it does I/O -- special case of namelist I/O.
35 
36    SUBROUTINE initial_config
37 !<DESCRIPTION>
38 ! This routine reads in the namelist.input file and sets
39 ! module_config_rec, a structure of TYPE(model_config_rec_type), which is is seen via USE association by any
40 ! subprogram that uses module_configure.  The module_config_rec structure
41 ! contains all namelist settings for all domains.  Variables that apply
42 ! to the entire run and have only one value regardless of domain are
43 ! scalars.  Variables that allow different settings for each domain are
44 ! defined as arrays of dimension max_domains (defined in
45 ! frame/module_driver_constants.F, from a setting passed in from
46 ! configure.wrf). There is another type in WRF, TYPE(grid_config_rec_type), in which
47 ! all fields pertain only to a single domain (and are all scalars). The subroutine
48 ! model_to_grid_config_rec(), also in frame/module_configure.F, is used to retrieve
49 ! the settings for a given domain from a TYPE(module_config_rec_type) and put them into
50 ! a TYPE(grid_config_rec_type), variables of which type are often called <em>config_flags</em>
51 ! in the WRF code.
52 ! 
53 ! Most of the code in this routine is generated from the Registry file
54 ! rconfig entries and included from the following files (found in the inc directory):
55 ! 
56 ! <pre>
57 ! namelist_defines.inc	declarations of namelist variables (local to this routine)
58 ! namelist_statements.inc	NAMELIST statements for each variable
59 ! namelist_defaults.inc	assignment to default values if specified in Registry
60 ! config_reads.inc		read statements for each namelist record
61 ! config_assigns.inc	assign each variable to field in module_config_rec
62 ! </pre>
63 !
64 !NOTE: generated subroutines from Registry file rconfig entries are renamed nl_
65 ! instead of rconfig_ due to length limits for subroutine names.
66 !
67 ! Note for version WRF 2.0: there is code here to force all domains to
68 ! have the same mp_physics setting. This is because different mp_physics
69 ! packages have different numbers of tracers but the nest forcing and
70 ! feedback code relies on the parent and nest having the same number and
71 ! kind of tracers. This means that the microphysics option
72 ! specified on the highest numbered domain is the microphysics
73 ! option for <em>all</em> domains in the run. This will be revisited.
74 ! 
75 !</DESCRIPTION>
76       IMPLICIT NONE
77 
78       INTEGER              :: io_status
79       INTEGER              :: i
80 
81       LOGICAL              :: nml_read_error
82 
83       CHARACTER (LEN=1024) :: nml_name
84 
85       INTEGER, PARAMETER :: nml_write_unit= 9
86       INTEGER, PARAMETER :: nml_read_unit = 10
87 
88 
89 ! define as temporaries
90 #include <namelist_defines.inc>
91 
92 ! Statements that specify the namelists
93 #include <namelist_statements.inc>
94 
95       OPEN ( UNIT   = nml_read_unit    ,      &
96              FILE   = "namelist.input" ,      &
97              FORM   = "FORMATTED"      ,      &
98              STATUS = "OLD"            ,      &
99              IOSTAT = io_status         )
100 
101       IF ( io_status .NE. 0 ) THEN
102         CALL WRF_ERROR_FATAL ( 'ERROR OPENING namelist.input' )
103       ENDIF
104 
105 #ifndef NO_NAMELIST_PRINT
106       OPEN ( UNIT   = nml_write_unit    ,      &
107              FILE   = "namelist.output" ,      &
108              FORM   = "FORMATTED"      ,      &
109              STATUS = "REPLACE"        ,      &
110              IOSTAT = io_status         )
111 
112       IF ( io_status .NE. 0 ) THEN
113         CALL WRF_ERROR_FATAL ( 'ERROR OPENING namelist.output' )
114       ENDIF
115 #endif
116 
117 ! Statements that set the namelist vars to default vals
118 #  include <namelist_defaults.inc>
119 
120 ! Statements that read the namelist are in this file
121 #  include <config_reads.inc>
122 
123 ! 2004/04/28  JM (with consensus by the group of developers)
124 ! This is needed to ensure that nesting will work, since
125 ! different mp_physics packages have different numbers of 
126 ! tracers. Basically, this says that the microphysics option
127 ! specified on the highest numbered domain *is* the microphysics
128 ! option for the run. Not the best solution but okay for 2.0.
129 !
130 
131       DO i = 1, max_dom
132          mp_physics(i) = mp_physics(max_dom)
133       ENDDO
134 
135 ! Statements that assign the variables to the cfg record are in this file
136 ! except the namelist_derived variables where are assigned below
137 #undef SOURCE_RECORD
138 #undef DEST_RECORD
139 #undef SOURCE_REC_DEX
140 #define SOURCE_RECORD 
141 #define DEST_RECORD model_config_rec %
142 #define SOURCE_REC_DEX
143 #include <config_assigns.inc>
144 
145 #ifdef PLANET
146 !***************** special conversion for timesteps *********************
147 ! 2004-12-07 ADT Notes
148 ! NB: P2SI needs to defined in multiple places.  Right now this
149 ! requirement is a kludge, and if I can find something more elegant
150 ! I will try to implement it later.
151 !
152 ! Beware: dt as the namelist timestep is now obsolete.  The new
153 ! variable "timestep" (which is an *integer* number of seconds),
154 ! with the (optional) additional specification of a fraction (to
155 ! make non-integer timesteps) now acts as the true timestep.
156 ! In share/set_timekeeping.F the integer(s) are converted to a real
157 ! number and put back in dt anyway!
158 ! We will deal with the case of the integer variables in
159 ! share/set_timekeeping.F itself.  For now, since they left dt in
160 ! the namelist definition, I will leave this here just in case ...
161       model_config_rec%dt    = dt    * P2SI
162 ! All of the following variables are told to be input in *MINUTES*
163 ! These values are converted to units of timesteps in the various
164 ! init routines in phys/module_physics_init.F by dividing by the
165 ! formula STEP = (xxDT*60./dt).  So it seems safe to multiply them
166 ! by P2SI here (with the exception of adding roundoff error later).
167 ! See notes in phys/module_radiation_driver for the radt example.
168       model_config_rec%radt  = radt  * P2SI
169       model_config_rec%bldt  = bldt  * P2SI
170       model_config_rec%cudt  = cudt  * P2SI
171       model_config_rec%gsmdt = gsmdt * P2SI
172 !************************************************************************
173 #endif
174 
175       CLOSE ( UNIT = nml_read_unit , IOSTAT = io_status )
176 
177       IF ( io_status .NE. 0 ) THEN
178         CALL WRF_ERROR_FATAL ( 'ERROR CLOSING namelist.input' )
179       ENDIF
180 
181 #ifndef NO_NAMELIST_PRINT
182       CLOSE ( UNIT = nml_write_unit , IOSTAT = io_status )
183 
184       IF ( io_status .NE. 0 ) THEN
185         CALL WRF_ERROR_FATAL ( 'ERROR CLOSING namelist.output' )
186       ENDIF
187 #endif
188 
189       RETURN
190 
191    END SUBROUTINE initial_config
192 
193 #if 1
194    SUBROUTINE get_config_as_buffer( buffer, buflen, ncopied )
195 ! note that model_config_rec_type must be defined as a sequence derived type
196       INTEGER,   INTENT(INOUT) ::  buffer(*)
197       INTEGER,   INTENT(IN)    ::  buflen
198       INTEGER,   INTENT(OUT)   ::  ncopied
199 !      TYPE(model_config_rec_type) :: model_config_rec
200       INTEGER :: nbytes
201       CALL wrf_num_bytes_between ( model_config_rec%last_item_in_struct ,   &
202                                    model_config_rec%first_item_in_struct ,  &
203                                    nbytes )
204 !      nbytes = loc(model_config_rec%last_item_in_struct) - &
205 !               loc(model_config_rec%first_item_in_struct)
206       IF ( nbytes .gt. buflen ) THEN
207         CALL wrf_error_fatal( &
208         "get_config_rec_as_buffer: buffer size too small for config_rec" )
209       ENDIF
210       CALL wrf_mem_copy( model_config_rec, buffer, nbytes )
211       ncopied = nbytes
212       RETURN
213    END SUBROUTINE get_config_as_buffer
214 
215    SUBROUTINE set_config_as_buffer( buffer, buflen )
216 ! note that model_config_rec_type must be defined as a sequence derived type
217       INTEGER,   INTENT(INOUT) ::  buffer(*)
218       INTEGER,   INTENT(IN)    ::  buflen
219 !      TYPE(model_config_rec_type) :: model_config_rec
220       INTEGER :: nbytes
221       CALL wrf_num_bytes_between ( model_config_rec%last_item_in_struct ,  &
222                                    model_config_rec%first_item_in_struct , &
223                                    nbytes )
224 !      nbytes = loc(model_config_rec%last_item_in_struct) - &
225 !               loc(model_config_rec%first_item_in_struct)
226       IF ( nbytes .gt. buflen ) THEN
227         CALL wrf_error_fatal( &
228         "set_config_rec_as_buffer: buffer length too small to fill model config record" )
229       ENDIF
230       CALL wrf_mem_copy( buffer, model_config_rec, nbytes )
231       RETURN
232    END SUBROUTINE set_config_as_buffer
233 #else
234    SUBROUTINE get_config_as_buffer( buffer, buflen, ncopied )
235 ! note that model_config_rec_type must be defined as a sequence derived type
236       INTEGER*1, INTENT(INOUT) ::  buffer(*)
237       INTEGER,   INTENT(IN)    ::  buflen
238       INTEGER,   INTENT(OUT)   ::  ncopied
239 !      TYPE(model_config_rec_type) :: model_config_rec
240       INTEGER :: nbytes
241       nbytes = loc(model_config_rec%last_item_in_struct) - &
242                loc(model_config_rec%first_item_in_struct)
243       IF ( nbytes .gt. buflen ) THEN
244         CALL wrf_error_fatal( &
245         "get_config_rec_as_buffer: buffer size too small for config_rec" )
246       ENDIF
247       CALL wrf_mem_copy( model_config_rec, buffer, nbytes )
248       ncopied = nbytes
249       RETURN
250    END SUBROUTINE get_config_as_buffer
251 
252    SUBROUTINE set_config_as_buffer( buffer, buflen )
253 ! note that model_config_rec_type must be defined as a sequence derived type
254       INTEGER*1, INTENT(INOUT) ::  buffer(*)
255       INTEGER,   INTENT(IN)    ::  buflen
256 !      TYPE(model_config_rec_type) :: model_config_rec
257       INTEGER :: nbytes
258       nbytes = loc(model_config_rec%last_item_in_struct) - &
259                loc(model_config_rec%first_item_in_struct)
260       IF ( nbytes .gt. buflen ) THEN
261         CALL wrf_error_fatal( &
262         "set_config_rec_as_buffer: buffer length too small to fill model config record" )
263       ENDIF
264       CALL wrf_mem_copy( buffer, model_config_rec, nbytes )
265       RETURN
266    END SUBROUTINE set_config_as_buffer
267 #endif
268 
269    SUBROUTINE model_to_grid_config_rec ( id_id , model_config_rec , grid_config_rec )
270       INTEGER , INTENT(IN)                         ::  id_id
271       TYPE ( model_config_rec_type ) , INTENT(IN)  ::  model_config_rec
272       TYPE ( grid_config_rec_type  ) , INTENT(OUT) ::  grid_config_rec
273 ! <DESCRIPTION>
274 ! This routine is called to populate a domain specific configuration
275 ! record of TYPE(grid_config_rec_type) with the configuration information
276 ! for that domain that is stored in TYPE(model_config_rec). Both types
277 ! are defined in frame/module_configure.F.  The input argument is the
278 ! record of type model_config_rec_type contains the model-wide
279 ! configuration information (that is, settings that apply to the model in
280 ! general) and configuration information for each individual domain.  The
281 ! output argument is the record of type grid_config_rec_type which
282 ! contains the model-wide configuration information and the
283 ! domain-specific information for this domain only.  In the
284 ! model_config_rec, the domain specific information is arrays, indexed by
285 ! the grid id's.  In the grid_config_rec the domain-specific information
286 ! is scalar and for the specific domain.  The first argument to this
287 ! routine is the grid id (top-most domain is always 1) as specified in
288 ! the domain-specific namelist variable grid_id.
289 ! 
290 ! The actual assignments form the model_config_rec_type to the
291 ! grid_config_rec_type are generate from the rconfig entries in the
292 ! Registry file and included by this routine from the file
293 ! inc/config_assigns.inc.
294 !
295 !NOTE: generated subroutines from Registry file rconfig entries are renamed nl_
296 ! instead of rconfig_ due to length limits for subroutine names.
297 !
298 ! 
299 ! </DESCRIPTION>
300 #undef SOURCE_RECORD
301 #undef SOURCE_REC_DEX
302 #undef DEST_RECORD
303 #define SOURCE_RECORD model_config_rec %
304 #define SOURCE_REC_DEX (id_id)
305 #define DEST_RECORD   grid_config_rec %
306 #include <config_assigns.inc>
307    END SUBROUTINE model_to_grid_config_rec
308 
309 
310    FUNCTION in_use_for_config ( id, vname ) RESULT ( in_use )
311      INTEGER, INTENT(IN) :: id 
312      CHARACTER*(*), INTENT(IN) :: vname
313      LOGICAL in_use
314      INTEGER uses 
315 
316      uses = 0 
317      in_use = .TRUE.
318 
319 #  include <in_use_for_config.inc>
320         
321      RETURN
322    END FUNCTION
323         
324 
325 ! Include the definitions of all the routines that return a namelist values
326 ! back to the driver. These are generated by the registry
327 
328    SUBROUTINE init_module_configure
329      IMPLICIT NONE
330      ! Local vars
331 
332      INTEGER i , j
333 
334      DO j = 1, max_domains
335 #include <scalar_tables_init.inc>
336      END DO
337    END SUBROUTINE init_module_configure
338 
339 ! When the compiler has Intel Inside (TM) (that is, ifort), the large
340 ! number of nl_get and nl_set routines inside the module causes the
341 ! compiler to never finish with this routine. For ifort, move the
342 ! routines outside the module. Note, the registry generates a 
343 ! USE module_configure for all the nl_get and nl_set routines
344 ! if IFORT_KLUDGE is in effect.
345 #ifdef IFORT_KLUDGE
346 
347 END MODULE module_configure
348 
349 # include <get_nl_config.inc>
350 
351 #else
352 
353 # include <get_nl_config.inc>
354 
355 END MODULE module_configure
356 
357 #endif
358 
359 ! Special (outside registry)
360 SUBROUTINE nl_get_mminlu ( idum , retval )
361   USE module_configure
362   CHARACTER(LEN=4)  :: retval
363   INTEGER idum
364   retval(1:4) = mminlu(1:4)   ! mminlu is defined in module_configure
365   RETURN
366 END SUBROUTINE nl_get_mminlu
367 SUBROUTINE nl_set_mminlu ( idum, inval )
368   USE module_configure
369   CHARACTER(LEN=4) :: inval
370   INTEGER idum
371   mminlu(1:4) = inval(1:4)    ! mminlu is defined in module_configure
372   RETURN
373 END SUBROUTINE nl_set_mminlu
374 
375 
376 SUBROUTINE set_scalar_indices_from_config ( idomain , dummy2, dummy1 )
377   USE module_driver_constants
378   USE module_state_description
379   USE module_wrf_error
380   USE module_configure
381   IMPLICIT NONE
382   INTEGER , INTENT(IN)  :: idomain
383   INTEGER               :: dummy1
384   INTEGER               :: dummy2
385 
386 !<DESCRIPTION>
387 !This routine is called to adjust the integer variables that are defined
388 !in frame/module_state_description.F (Registry-generated) and that serve
389 !as indices into 4D tracer arrays for moisture, chemistry, etc.
390 !Different domains (different grid data structures) are allowed to have
391 !different sets of tracers so these indices can vary from domain to
392 !domain. However, since the indices are defined globally in
393 !module_state_description (a shortcoming in the current software), it is
394 !necessary that these indices be reset each time a different grid is to
395 !be computed on.
396 !
397 !The scalar idices are set according to the particular physics
398 !packages -- more specifically in the case of the moisture tracers, microphysics
399 !packages -- that are stored for each domain in model_config_rec and
400 !indexed by the grid id, passed in as an argument to this routine.  (The
401 !initial_config() routine in module_configure is what reads the
402 !namelist.input file and sets model_config_rec.)
403 !
404 !The actual code for calculating the scalar indices on a particular
405 !domain is generated from the Registry state array definitions for the
406 !4d tracers and from the package definitions that indicate which physics
407 !packages use which tracers.
408 !
409 !</DESCRIPTION>
410 
411 #include <scalar_indices.inc>
412 #include <scalar_indices_init.inc>
413   RETURN
414 END SUBROUTINE set_scalar_indices_from_config