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       INTEGER, PARAMETER :: nml_write_unit= 9
82       INTEGER, PARAMETER :: nml_read_unit = 10
83 
84 ! define as temporaries
85 #include <namelist_defines.inc>
86 
87 ! Statements that specify the namelists
88 #include <namelist_statements.inc>
89 
90       OPEN ( UNIT   = nml_read_unit    ,      &
91              FILE   = "namelist.input" ,      &
92              FORM   = "FORMATTED"      ,      &
93              STATUS = "OLD"            ,      &
94              IOSTAT = io_status         )
95 
96       IF ( io_status .NE. 0 ) THEN
97         CALL WRF_ERROR_FATAL ( 'ERROR OPENING namelist.input' )
98       ENDIF
99 
100 ! Statements that set the namelist vars to default vals
101 #  include <namelist_defaults.inc>
102 
103 ! Statements that read the namelist are in this file
104 #  include <config_reads.inc>
105 
106 ! 2004/04/28  JM (with consensus by the group of developers)
107 ! This is needed to ensure that nesting will work, since
108 ! different mp_physics packages have different numbers of 
109 ! tracers. Basically, this says that the microphysics option
110 ! specified on the highest numbered domain *is* the microphysics
111 ! option for the run. Not the best solution but okay for 2.0.
112 !
113 
114       DO i = 1, max_dom
115          mp_physics(i) = mp_physics(max_dom)
116       ENDDO
117 
118 ! Statements that assign the variables to the cfg record are in this file
119 ! except the namelist_derived variables where are assigned below
120 #undef SOURCE_RECORD
121 #undef DEST_RECORD
122 #undef SOURCE_REC_DEX
123 #define SOURCE_RECORD 
124 #define DEST_RECORD model_config_rec %
125 #define SOURCE_REC_DEX
126 #include <config_assigns.inc>
127 
128       CLOSE ( UNIT = nml_read_unit , IOSTAT = io_status )
129 
130       IF ( io_status .NE. 0 ) THEN
131         CALL WRF_ERROR_FATAL ( 'ERROR CLOSING namelist.input' )
132       ENDIF
133 
134       RETURN
135 
136    END SUBROUTINE initial_config
137 
138 #if 1
139    SUBROUTINE get_config_as_buffer( buffer, buflen, ncopied )
140 ! note that model_config_rec_type must be defined as a sequence derived type
141       INTEGER,   INTENT(INOUT) ::  buffer(*)
142       INTEGER,   INTENT(IN)    ::  buflen
143       INTEGER,   INTENT(OUT)   ::  ncopied
144 !      TYPE(model_config_rec_type) :: model_config_rec
145       INTEGER :: nbytes
146       CALL wrf_num_bytes_between ( model_config_rec%last_item_in_struct ,   &
147                                    model_config_rec%first_item_in_struct ,  &
148                                    nbytes )
149 !      nbytes = loc(model_config_rec%last_item_in_struct) - &
150 !               loc(model_config_rec%first_item_in_struct)
151       IF ( nbytes .gt. buflen ) THEN
152         CALL wrf_error_fatal( &
153         "get_config_rec_as_buffer: buffer size to small for config_rec" )
154       ENDIF
155       CALL wrf_mem_copy( model_config_rec, buffer, nbytes )
156       ncopied = nbytes
157       RETURN
158    END SUBROUTINE get_config_as_buffer
159 
160    SUBROUTINE set_config_as_buffer( buffer, buflen )
161 ! note that model_config_rec_type must be defined as a sequence derived type
162       INTEGER,   INTENT(INOUT) ::  buffer(*)
163       INTEGER,   INTENT(IN)    ::  buflen
164 !      TYPE(model_config_rec_type) :: model_config_rec
165       INTEGER :: nbytes
166       CALL wrf_num_bytes_between ( model_config_rec%last_item_in_struct ,  &
167                                    model_config_rec%first_item_in_struct , &
168                                    nbytes )
169 !      nbytes = loc(model_config_rec%last_item_in_struct) - &
170 !               loc(model_config_rec%first_item_in_struct)
171       IF ( nbytes .gt. buflen ) THEN
172         CALL wrf_error_fatal( &
173         "set_config_rec_as_buffer: buffer length too small to fill model config record" )
174       ENDIF
175       CALL wrf_mem_copy( buffer, model_config_rec, nbytes )
176       RETURN
177    END SUBROUTINE set_config_as_buffer
178 #else
179    SUBROUTINE get_config_as_buffer( buffer, buflen, ncopied )
180 ! note that model_config_rec_type must be defined as a sequence derived type
181       INTEGER*1, INTENT(INOUT) ::  buffer(*)
182       INTEGER,   INTENT(IN)    ::  buflen
183       INTEGER,   INTENT(OUT)   ::  ncopied
184 !      TYPE(model_config_rec_type) :: model_config_rec
185       INTEGER :: nbytes
186       nbytes = loc(model_config_rec%last_item_in_struct) - &
187                loc(model_config_rec%first_item_in_struct)
188       IF ( nbytes .gt. buflen ) THEN
189         CALL wrf_error_fatal( &
190         "get_config_rec_as_buffer: buffer size to small for config_rec" )
191       ENDIF
192       CALL wrf_mem_copy( model_config_rec, buffer, nbytes )
193       ncopied = nbytes
194       RETURN
195    END SUBROUTINE get_config_as_buffer
196 
197    SUBROUTINE set_config_as_buffer( buffer, buflen )
198 ! note that model_config_rec_type must be defined as a sequence derived type
199       INTEGER*1, INTENT(INOUT) ::  buffer(*)
200       INTEGER,   INTENT(IN)    ::  buflen
201 !      TYPE(model_config_rec_type) :: model_config_rec
202       INTEGER :: nbytes
203       nbytes = loc(model_config_rec%last_item_in_struct) - &
204                loc(model_config_rec%first_item_in_struct)
205       IF ( nbytes .gt. buflen ) THEN
206         CALL wrf_error_fatal( &
207         "set_config_rec_as_buffer: buffer length too small to fill model config record" )
208       ENDIF
209       CALL wrf_mem_copy( buffer, model_config_rec, nbytes )
210       RETURN
211    END SUBROUTINE set_config_as_buffer
212 #endif
213 
214    SUBROUTINE model_to_grid_config_rec ( id_id , model_config_rec , grid_config_rec )
215       INTEGER , INTENT(IN)                         ::  id_id
216       TYPE ( model_config_rec_type ) , INTENT(IN)  ::  model_config_rec
217       TYPE ( grid_config_rec_type  ) , INTENT(OUT) ::  grid_config_rec
218 ! <DESCRIPTION>
219 ! This routine is called to populate a domain specific configuration
220 ! record of TYPE(grid_config_rec_type) with the configuration information
221 ! for that domain that is stored in TYPE(model_config_rec). Both types
222 ! are defined in frame/module_configure.F.  The input argument is the
223 ! record of type model_config_rec_type contains the model-wide
224 ! configuration information (that is, settings that apply to the model in
225 ! general) and configuration information for each individual domain.  The
226 ! output argument is the record of type grid_config_rec_type which
227 ! contains the model-wide configuration information and the
228 ! domain-specific information for this domain only.  In the
229 ! model_config_rec, the domain specific information is arrays, indexed by
230 ! the grid id's.  In the grid_config_rec the domain-specific information
231 ! is scalar and for the specific domain.  The first argument to this
232 ! routine is the grid id (top-most domain is always 1) as specified in
233 ! the domain-specific namelist variable grid_id.
234 ! 
235 ! The actual assignments form the model_config_rec_type to the
236 ! grid_config_rec_type are generate from the rconfig entries in the
237 ! Registry file and included by this routine from the file
238 ! inc/config_assigns.inc.
239 !
240 !NOTE: generated subroutines from Registry file rconfig entries are renamed nl_
241 ! instead of rconfig_ due to length limits for subroutine names.
242 !
243 ! 
244 ! </DESCRIPTION>
245 #undef SOURCE_RECORD
246 #undef SOURCE_REC_DEX
247 #undef DEST_RECORD
248 #define SOURCE_RECORD model_config_rec %
249 #define SOURCE_REC_DEX (id_id)
250 #define DEST_RECORD   grid_config_rec %
251 #include <config_assigns.inc>
252    END SUBROUTINE model_to_grid_config_rec
253 
254 ! Include the definitions of all the routines that return a namelist values
255 ! back to the driver. These are generated by the registry
256 
257    SUBROUTINE init_module_configure
258      IMPLICIT NONE
259      ! Local vars
260 
261      INTEGER i , j
262 
263      DO j = 1, max_domains
264 #include <scalar_tables_init.inc>
265      END DO
266    END SUBROUTINE init_module_configure
267 
268 ! When the compiler has Intel Inside (TM) (that is, ifort), the large
269 ! number of nl_get and nl_set routines inside the module causes the
270 ! compiler to never finish with this routine. For ifort, move the
271 ! routines outside the module. Note, the registry generates a 
272 ! USE module_configure for all the nl_get and nl_set routines
273 ! if IFORT_KLUDGE is in effect.
274 #ifdef IFORT_KLUDGE
275 
276 END MODULE module_configure
277 
278 # include <get_nl_config.inc>
279 
280 #else
281 
282 # include <get_nl_config.inc>
283 
284 END MODULE module_configure
285 
286 #endif
287 
288 ! Special (outside registry)
289 SUBROUTINE nl_get_mminlu ( idum , retval )
290   USE module_configure
291   CHARACTER(LEN=4)  :: retval
292   INTEGER idum
293   retval(1:4) = mminlu(1:4)   ! mminlu is defined in module_configure
294   RETURN
295 END SUBROUTINE nl_get_mminlu
296 SUBROUTINE nl_set_mminlu ( idum, inval )
297   USE module_configure
298   CHARACTER(LEN=4) :: inval
299   INTEGER idum
300   mminlu(1:4) = inval(1:4)    ! mminlu is defined in module_configure
301   RETURN
302 END SUBROUTINE nl_set_mminlu
303 
304 
305 SUBROUTINE set_scalar_indices_from_config ( idomain , dummy2, dummy1 )
306   USE module_driver_constants
307   USE module_state_description
308   USE module_wrf_error
309   USE module_configure
310   IMPLICIT NONE
311   INTEGER , INTENT(IN)  :: idomain
312   INTEGER               :: dummy1
313   INTEGER               :: dummy2
314 
315 !<DESCRIPTION>
316 !This routine is called to adjust the integer variables that are defined
317 !in frame/module_state_description.F (Registry-generated) and that serve
318 !as indices into 4D tracer arrays for moisture, chemistry, etc.
319 !Different domains (different grid data structures) are allowed to have
320 !different sets of tracers so these indices can vary from domain to
321 !domain. However, since the indices are defined globally in
322 !module_state_description (a shortcoming in the current software), it is
323 !necessary that these indices be reset each time a different grid is to
324 !be computed on.
325 !
326 !The scalar idices are set according to the particular physics
327 !packages -- more specifically in the case of the moisture tracers, microphysics
328 !packages -- that are stored for each domain in model_config_rec and
329 !indexed by the grid id, passed in as an argument to this routine.  (The
330 !initial_config() routine in module_configure is what reads the
331 !namelist.input file and sets model_config_rec.)
332 !
333 !The actual code for calculating the scalar indices on a particular
334 !domain is generated from the Registry state array definitions for the
335 !4d tracers and from the package definitions that indicate which physics
336 !packages use which tracers.
337 !
338 !</DESCRIPTION>
339 
340 #include <scalar_indices.inc>
341 #include <scalar_indices_init.inc>
342   RETURN
343 END SUBROUTINE set_scalar_indices_from_config