source: trunk/WRF.COMMON/WRFV2/frame/module_configure.F @ 3532

Last change on this file since 3532 was 11, checked in by aslmd, 15 years ago

spiga@svn-planeto:ajoute le modele meso-echelle martien

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