source: lmdz_wrf/WRFV3/frame/module_configure.F @ 1

Last change on this file since 1 was 1, checked in by lfita, 10 years ago
  • -- --- Opening of the WRF+LMDZ coupling repository --- -- -

WRF: version v3.3
LMDZ: version v1818

More details in:

File size: 20.7 KB
Line 
1!WRF:DRIVER_LAYER:CONFIGURATION
2!
3
4MODULE module_scalar_tables
5  USE module_driver_constants
6  USE module_state_description
7  USE module_domain_type, ONLY : streamrec
8#include <scalar_tables.inc>
9CONTAINS
10  SUBROUTINE init_module_scalar_tables
11     INTEGER i , j
12     DO j = 1, max_domains
13#include <scalar_tables_init.inc>
14     END DO
15  END SUBROUTINE init_module_scalar_tables
16END MODULE module_scalar_tables
17
18MODULE module_configure
19
20   USE module_driver_constants
21   USE module_state_description
22   USE module_wrf_error
23
24   TYPE model_config_rec_type
25      SEQUENCE
26! Statements that declare namelist variables are in this file
27! Note that the namelist is SEQUENCE and generated such that the first item is an
28! integer, first_item_in_struct and the last is an integer last_item_in_struct
29! this provides a way of converting this to a buffer for passing to and from
30! the driver.
31#include <namelist_defines.inc>
32   END TYPE model_config_rec_type
33
34   TYPE grid_config_rec_type
35#include <namelist_defines2.inc>
36   END TYPE grid_config_rec_type
37
38   TYPE(model_config_rec_type) :: model_config_rec
39
40!#include <scalar_tables.inc>
41
42! special entries (put here but not enshrined in Registry for one reason or other)
43
44!   CHARACTER (LEN=256) :: mminlu = ' '             ! character string for landuse table
45
46CONTAINS
47
48
49! Model layer, even though it does I/O -- special case of namelist I/O.
50
51   SUBROUTINE initial_config
52!<DESCRIPTION>
53! This routine reads in the namelist.input file and sets
54! module_config_rec, a structure of TYPE(model_config_rec_type), which is is seen via USE association by any
55! subprogram that uses module_configure.  The module_config_rec structure
56! contains all namelist settings for all domains.  Variables that apply
57! to the entire run and have only one value regardless of domain are
58! scalars.  Variables that allow different settings for each domain are
59! defined as arrays of dimension max_domains (defined in
60! frame/module_driver_constants.F, from a setting passed in from
61! configure.wrf). There is another type in WRF, TYPE(grid_config_rec_type), in which
62! all fields pertain only to a single domain (and are all scalars). The subroutine
63! model_to_grid_config_rec(), also in frame/module_configure.F, is used to retrieve
64! the settings for a given domain from a TYPE(module_config_rec_type) and put them into
65! a TYPE(grid_config_rec_type), variables of which type are often called <em>config_flags</em>
66! in the WRF code.
67!
68! Most of the code in this routine is generated from the Registry file
69! rconfig entries and included from the following files (found in the inc directory):
70!
71! <pre>
72! namelist_defines.inc  declarations of namelist variables (local to this routine)
73! namelist_statements.inc       NAMELIST statements for each variable
74! namelist_defaults.inc assignment to default values if specified in Registry
75! config_reads.inc              read statements for each namelist record
76! config_assigns.inc    assign each variable to field in module_config_rec
77! </pre>
78!
79!NOTE: generated subroutines from Registry file rconfig entries are renamed nl_
80! instead of rconfig_ due to length limits for subroutine names.
81!
82! Note for version WRF 2.0: there is code here to force all domains to
83! have the same mp_physics setting. This is because different mp_physics
84! packages have different numbers of tracers but the nest forcing and
85! feedback code relies on the parent and nest having the same number and
86! kind of tracers. This means that the microphysics option
87! specified on the highest numbered domain is the microphysics
88! option for <em>all</em> domains in the run. This will be revisited.
89!
90!</DESCRIPTION>
91      IMPLICIT NONE
92
93      INTEGER              :: io_status
94      INTEGER              :: i
95
96      LOGICAL              :: nml_read_error
97
98      CHARACTER (LEN=1024) :: nml_name
99
100      INTEGER, PARAMETER :: nml_write_unit= 9
101      INTEGER, PARAMETER :: nml_read_unit = 10
102
103
104! define as temporaries
105#include <namelist_defines.inc>
106
107! Statements that specify the namelists
108#include <namelist_statements.inc>
109
110      OPEN ( UNIT   = nml_read_unit    ,      &
111             FILE   = "namelist.input" ,      &
112             FORM   = "FORMATTED"      ,      &
113             STATUS = "OLD"            ,      &
114             IOSTAT = io_status         )
115
116      IF ( io_status .NE. 0 ) THEN
117        CALL WRF_ERROR_FATAL ( 'ERROR OPENING namelist.input' )
118      ENDIF
119
120#ifndef NO_NAMELIST_PRINT
121      OPEN ( UNIT   = nml_write_unit    ,      &
122             FILE   = "namelist.output" ,      &
123             FORM   = "FORMATTED"      ,      &
124             STATUS = "REPLACE"        ,      &
125             IOSTAT = io_status         )
126
127      IF ( io_status .NE. 0 ) THEN
128        CALL WRF_ERROR_FATAL ( 'ERROR OPENING namelist.output' )
129      ENDIF
130#endif
131
132! Statements that set the namelist vars to default vals
133#  include <namelist_defaults.inc>
134
135#if (DA_CORE == 1)
136! Override the default values, because we can not assigned a arrary with different values in registry.
137
138      as1(1:3) = (/ 0.25, 1.0, 1.5 /)
139      as2(1:3) = (/ 0.25, 1.0, 1.5 /)
140      as3(1:3) = (/ 0.25, 1.0, 1.5 /)
141      as4(1:3) = (/ 0.25, 1.0, 1.5 /)
142      as5(1:3) = (/ 0.25, 1.0, 1.5 /)
143#endif
144
145! Statements that read the namelist are in this file
146#  include <config_reads.inc>
147
148! 2004/04/28  JM (with consensus by the group of developers)
149! This is needed to ensure that nesting will work, since
150! different mp_physics packages have different numbers of
151! tracers. Basically, this says that the microphysics option
152! specified on the highest numbered domain *is* the microphysics
153! option for the run. Not the best solution but okay for 2.0.
154!
155
156      DO i = 1, max_dom
157         mp_physics(i) = mp_physics(max_dom)
158      ENDDO
159
160! Statements that assign the variables to the cfg record are in this file
161! except the namelist_derived variables where are assigned below
162#undef SOURCE_RECORD
163#undef DEST_RECORD
164#undef SOURCE_REC_DEX
165#define SOURCE_RECORD
166#define DEST_RECORD model_config_rec %
167#define SOURCE_REC_DEX
168#include <config_assigns.inc>
169
170
171      CLOSE ( UNIT = nml_read_unit , IOSTAT = io_status )
172
173      IF ( io_status .NE. 0 ) THEN
174        CALL WRF_ERROR_FATAL ( 'ERROR CLOSING namelist.input' )
175      ENDIF
176
177#ifndef NO_NAMELIST_PRINT
178      CLOSE ( UNIT = nml_write_unit , IOSTAT = io_status )
179
180      IF ( io_status .NE. 0 ) THEN
181        CALL WRF_ERROR_FATAL ( 'ERROR CLOSING namelist.output' )
182      ENDIF
183#endif
184
185#ifdef _WIN32
186      model_config_rec%nocolons = .TRUE.   ! always no colons for Windows
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     IF      ( vname(1:1) .GE. 'x' ) THEN
320#  include <in_use_for_config_xz.inc>
321     ELSE IF ( vname(1:1) .GE. 't' ) THEN
322#  include <in_use_for_config_tw.inc>
323     ELSE IF ( vname(1:1) .GE. 'o' ) THEN
324#  include <in_use_for_config_os.inc>
325     ELSE IF ( vname(1:1) .GE. 'l' ) THEN
326#  include <in_use_for_config_ln.inc>
327     ELSE IF ( vname(1:1) .GE. 'g' ) THEN
328#  include <in_use_for_config_gk.inc>
329     ELSE IF ( vname(1:1) .GE. 'd' ) THEN
330#  include <in_use_for_config_df.inc>
331     ELSE
332#  include <in_use_for_config_ac.inc>
333     ENDIF
334
335     RETURN
336   END FUNCTION
337
338
339! Include the definitions of all the routines that return a namelist values
340! back to the driver. These are generated by the registry
341
342   SUBROUTINE init_module_configure
343     USE module_scalar_tables
344     IMPLICIT NONE
345     CALL init_module_scalar_tables
346   END SUBROUTINE init_module_configure
347
348   SUBROUTINE wrf_alt_nml_obsolete (nml_read_unit, nml_name)
349!
350!<DESCRIPTION>
351! If there is an error reading the "nml_name" namelist, this routine is
352! called to check for namelist variables that have been removed by the
353! developers and are still in user's namelists.
354!
355! The calls to this routine are in registry-generated code: inc/config_reads.inc
356!</DESCRIPTION>
357!
358     IMPLICIT NONE
359     INTEGER, INTENT(IN)       :: nml_read_unit
360     CHARACTER*(*), INTENT(IN) :: nml_name
361     INTEGER                   :: nml_error
362
363#include <namelist_defines.inc>
364#include <namelist_statements.inc>
365
366! These are the variables that have been removed
367     logical , DIMENSION(max_domains) :: pd_moist, pd_chem, pd_tke, pd_scalar
368     NAMELIST /dynamics/                 pd_moist, pd_chem, pd_tke, pd_scalar
369
370     integer , DIMENSION(max_domains) :: ucmcall
371     NAMELIST /physics/                  ucmcall
372
373     integer , DIMENSION(max_domains) :: obs_nobs_prt
374     NAMELIST /fdda/                     obs_nobs_prt
375
376     LOGICAL ::         global, print_detail_airep, print_detail_timing
377     NAMELIST /wrfvar1/ global, print_detail_airep, print_detail_timing
378
379     LOGICAL ::         write_qcw, write_qrn, write_qci, write_qsn
380     NAMELIST /wrfvar2/ write_qcw, write_qrn, write_qci, write_qsn
381     LOGICAL ::          write_qgr, write_filtered_obs
382     NAMELIST /wrfvar2/  write_qgr, write_filtered_obs
383
384     LOGICAL ::         use_eos_radobs
385     NAMELIST /wrfvar4/ use_eos_radobs
386
387     LOGICAL             :: use_crtm_kmatrix_fast
388     NAMELIST /wrfvar14/    use_crtm_kmatrix_fast
389     CHARACTER (LEN=256) :: spccoeff_file, taucoeff_file, aerosolcoeff_file
390     NAMELIST /wrfvar14/    spccoeff_file, taucoeff_file, aerosolcoeff_file
391     CHARACTER (LEN=256) :: cloudcoeff_file, emiscoeff_file
392     NAMELIST /wrfvar14/    cloudcoeff_file, emiscoeff_file
393
394
395
396! Read the namelist again, if it succeeds after adding the above variables,
397! it probably failed because these are still in the namelist.  If it fails
398! again, we will return.
399
400     REWIND ( UNIT = nml_read_unit )
401
402!----------------------------- dynamics ---------------------------------
403     if ( TRIM(nml_name) .eq. "dynamics" ) then
404
405        READ   ( UNIT = nml_read_unit , NML = dynamics , iostat=nml_error )
406
407        IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
408           CALL wrf_debug(0, "-- Are pd_moist, pd_chem, pd_tke, or pd_scalar still in your "// &
409                               TRIM(nml_name)//" namelist?")
410           CALL wrf_debug(0, "-- Replace them with moist_adv_opt, chem_adv_opt, tke_adv_opt "// &
411                             " and scalar_adv_opt, respectively.")
412        ENDIF
413
414!---------------------------------- physics -----------------------------
415     else if ( TRIM(nml_name) .eq. "physics" ) then
416
417        READ   ( UNIT = nml_read_unit , NML = physics , iostat=nml_error )
418
419        IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
420           CALL wrf_debug(0, "-- Is ucmcall still in your "// TRIM(nml_name)//" namelist?")
421           CALL wrf_debug(0, "-- Replace it with sf_urban_physics")
422        ENDIF
423
424!---------------------------------- fdda --------------------------------
425     else if ( TRIM(nml_name) .eq. "fdda" ) then
426
427        READ   ( UNIT = nml_read_unit , NML = fdda , iostat=nml_error )
428
429        IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
430           CALL wrf_debug(0, "-- Is obs_nobs_prt still in your "// TRIM(nml_name)//" namelist?")
431           CALL wrf_debug(0, "-- Replace it with obs_prt_max")
432        ENDIF
433
434!---------------------------------- wrfvar1 -----------------------------
435     else if ( TRIM(nml_name) .eq. "wrfvar1" ) then
436
437        READ   ( UNIT = nml_read_unit , NML = wrfvar1 , iostat=nml_error )
438
439        IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
440           CALL wrf_debug(0, "-- Are global, print_detail_airep, print_detail_timing still in your "// &
441                              TRIM(nml_name)//" namelist?")
442           CALL wrf_debug(0, "-- Remove global, print_detail_airep, print_detail_timing "// &
443                             "from wrfvar1 namelist as they are obsolete.")
444        ENDIF
445
446!---------------------------------- wrfvar2 -----------------------------
447     else if ( TRIM(nml_name) .eq. "wrfvar2" ) then
448
449        READ   ( UNIT = nml_read_unit , NML = wrfvar2 , iostat=nml_error )
450
451        IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
452           CALL wrf_debug(0, "-- Are write_qcw, write_qrn, write_qci, write_qsn, write_qgr, "// &
453                             "write_filtered_obs still in your "// &
454                              TRIM(nml_name)//" namelist?")
455           CALL wrf_debug(0, "-- Remove write_qcw, write_qrn, write_qci, write_qsn, write_qgr, "// &
456                             "write_filtered_obs as they are obsolete.")
457        ENDIF
458
459!---------------------------------- wrfvar4 -----------------------------
460     else if ( TRIM(nml_name) .eq. "wrfvar4" ) then
461
462        READ   ( UNIT = nml_read_unit , NML = wrfvar4 , iostat=nml_error )
463
464        IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
465           CALL wrf_debug(0, "-- Is use_eos_radobs still in your "// &
466                              TRIM(nml_name)//" namelist?")
467           CALL wrf_debug(0, "-- Remove use_eos_radobs as it is obsolete.")
468        ENDIF
469
470!---------------------------------- wrfvar14 -----------------------------
471     else if ( TRIM(nml_name) .eq. "wrfvar14" ) then
472
473     READ   ( UNIT = nml_read_unit , NML = wrfvar14 , iostat=nml_error )
474
475        IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
476           CALL wrf_debug(0, "-- Are use_crtm_kmatrix_fast, spccoeff_file, taucoeff_file, "// &
477                             "aerosolcoeff_file, cloudcoeff_file, emiscoeff_file still in your "// &
478                              TRIM(nml_name)//" namelist?")
479           CALL wrf_debug(0, "-- Remove them as they are obsolete.")
480        ENDIF
481
482!---------------------------------- error -------------------------------
483     else
484         IF ( &
485#include "namelist_nametest.inc"
486              ) THEN
487            nml_error = 0
488         ELSE
489            CALL wrf_debug(0, TRIM(nml_name)//" is not a valid namelist name")
490         ENDIF
491     end if
492
493     IF ( nml_error .NE. 0 ) then    ! Still failed
494        return
495     ENDIF
496
497   END SUBROUTINE wrf_alt_nml_obsolete
498
499END MODULE module_configure
500
501
502SUBROUTINE set_scalar_indices_from_config ( idomain , dummy2, dummy1 )
503  USE module_driver_constants
504  USE module_state_description
505  USE module_wrf_error
506  USE module_configure, ONLY : model_config_rec
507  USE module_scalar_tables
508  IMPLICIT NONE
509  INTEGER , INTENT(IN)  :: idomain
510  INTEGER               :: dummy1
511  INTEGER               :: dummy2
512
513!<DESCRIPTION>
514!This routine is called to adjust the integer variables that are defined
515!in frame/module_state_description.F (Registry-generated) and that serve
516!as indices into 4D tracer arrays for moisture, chemistry, etc.
517!Different domains (different grid data structures) are allowed to have
518!different sets of tracers so these indices can vary from domain to
519!domain. However, since the indices are defined globally in
520!module_state_description (a shortcoming in the current software), it is
521!necessary that these indices be reset each time a different grid is to
522!be computed on.
523!
524!The scalar idices are set according to the particular physics
525!packages -- more specifically in the case of the moisture tracers, microphysics
526!packages -- that are stored for each domain in model_config_rec and
527!indexed by the grid id, passed in as an argument to this routine.  (The
528!initial_config() routine in module_configure is what reads the
529!namelist.input file and sets model_config_rec.)
530!
531!The actual code for calculating the scalar indices on a particular
532!domain is generated from the Registry state array definitions for the
533!4d tracers and from the package definitions that indicate which physics
534!packages use which tracers.
535!
536!</DESCRIPTION>
537
538#include <scalar_indices.inc>
539#include <scalar_indices_init.inc>
540  RETURN
541END SUBROUTINE set_scalar_indices_from_config
542
Note: See TracBrowser for help on using the repository browser.