!WRF:DRIVER_LAYER:CONFIGURATION
!


MODULE  module_scalar_tables (docs)   54
  USE module_driver_constants
  USE module_state_description
#include <scalar_tables.inc>
CONTAINS

  SUBROUTINE  init_module_scalar_tables (docs)   1,3
     INTEGER i , j
     DO j = 1, max_domains
#include <scalar_tables_init.inc>
     END DO
  END SUBROUTINE init_module_scalar_tables
END MODULE module_scalar_tables


MODULE  module_configure (docs)   2368

   USE module_driver_constants
   USE module_state_description
   USE module_wrf_error

   TYPE model_config_rec_type
      SEQUENCE
! Statements that declare namelist variables are in this file
! Note that the namelist is SEQUENCE and generated such that the first item is an
! integer, first_item_in_struct and the last is an integer last_item_in_struct
! this provides a way of converting this to a buffer for passing to and from
! the driver.
#include <namelist_defines.inc>
   END TYPE model_config_rec_type

   TYPE grid_config_rec_type
#include <namelist_defines2.inc>
   END TYPE grid_config_rec_type

   TYPE(model_config_rec_type) :: model_config_rec

!#include <scalar_tables.inc>

! special entries (put here but not enshrined in Registry for one reason or other)

!   CHARACTER (LEN=256) :: mminlu = ' '             ! character string for landuse table

CONTAINS


! Model layer, even though it does I/O -- special case of namelist I/O.


   SUBROUTINE  initial_config (docs)   16,4
!<DESCRIPTION>
! This routine reads in the namelist.input file and sets
! module_config_rec, a structure of TYPE(model_config_rec_type), which is is seen via USE association by any
! subprogram that uses module_configure.  The module_config_rec structure
! contains all namelist settings for all domains.  Variables that apply
! to the entire run and have only one value regardless of domain are
! scalars.  Variables that allow different settings for each domain are
! defined as arrays of dimension max_domains (defined in
! frame/module_driver_constants.F, from a setting passed in from
! configure.wrf). There is another type in WRF, TYPE(grid_config_rec_type), in which
! all fields pertain only to a single domain (and are all scalars). The subroutine
! model_to_grid_config_rec(), also in frame/module_configure.F, is used to retrieve
! the settings for a given domain from a TYPE(module_config_rec_type) and put them into
! a TYPE(grid_config_rec_type), variables of which type are often called <em>config_flags</em>
! in the WRF code.
!
! Most of the code in this routine is generated from the Registry file
! rconfig entries and included from the following files (found in the inc directory):
!
! <pre>
! namelist_defines.inc	declarations of namelist variables (local to this routine)
! namelist_statements.inc	NAMELIST statements for each variable
! namelist_defaults.inc	assignment to default values if specified in Registry
! config_reads.inc		read statements for each namelist record
! config_assigns.inc	assign each variable to field in module_config_rec
! </pre>
!
!NOTE: generated subroutines from Registry file rconfig entries are renamed nl_
! instead of rconfig_ due to length limits for subroutine names.
!
! Note for version WRF 2.0: there is code here to force all domains to
! have the same mp_physics setting. This is because different mp_physics
! packages have different numbers of tracers but the nest forcing and
! feedback code relies on the parent and nest having the same number and
! kind of tracers. This means that the microphysics option
! specified on the highest numbered domain is the microphysics
! option for <em>all</em> domains in the run. This will be revisited.
!
!</DESCRIPTION>
      IMPLICIT NONE

      INTEGER              :: io_status
      INTEGER              :: i

      LOGICAL              :: nml_read_error

      CHARACTER (LEN=1024) :: nml_name

      INTEGER, PARAMETER :: nml_write_unit= 9
      INTEGER, PARAMETER :: nml_read_unit = 10


! define as temporaries
#include <namelist_defines.inc>

! Statements that specify the namelists
#include <namelist_statements.inc>

      OPEN ( UNIT   = nml_read_unit    ,      &
             FILE   = "namelist.input" ,      &
             FORM   = "FORMATTED"      ,      &
             STATUS = "OLD"            ,      &
             IOSTAT = io_status         )

      IF ( io_status .NE. 0 ) THEN
        CALL WRF_ERROR_FATAL ( 'ERROR OPENING namelist.input' )
      ENDIF

#ifndef NO_NAMELIST_PRINT
      OPEN ( UNIT   = nml_write_unit    ,      &
             FILE   = "namelist.output" ,      &
             FORM   = "FORMATTED"      ,      &
             STATUS = "REPLACE"        ,      &
             IOSTAT = io_status         )

      IF ( io_status .NE. 0 ) THEN
        CALL WRF_ERROR_FATAL ( 'ERROR OPENING namelist.output' )
      ENDIF
#endif

! Statements that set the namelist vars to default vals
#  include <namelist_defaults.inc>

! Statements that read the namelist are in this file
#  include <config_reads.inc>

! 2004/04/28  JM (with consensus by the group of developers)
! This is needed to ensure that nesting will work, since
! different mp_physics packages have different numbers of
! tracers. Basically, this says that the microphysics option
! specified on the highest numbered domain *is* the microphysics
! option for the run. Not the best solution but okay for 2.0.
!

      DO i = 1, max_dom
         mp_physics(i) = mp_physics(max_dom)
      ENDDO

! Statements that assign the variables to the cfg record are in this file
! except the namelist_derived variables where are assigned below
#undef SOURCE_RECORD
#undef DEST_RECORD
#undef SOURCE_REC_DEX
#define SOURCE_RECORD
#define DEST_RECORD model_config_rec %
#define SOURCE_REC_DEX
#include <config_assigns.inc>

#ifdef PLANET
!***************** special conversion for timesteps *********************
! 2004-12-07 ADT Notes
! NB: P2SI needs to defined in multiple places.  Right now this
! requirement is a kludge, and if I can find something more elegant
! I will try to implement it later.
!
! Beware: dt as the namelist timestep is now obsolete.  The new
! variable "timestep" (which is an *integer* number of seconds),
! with the (optional) additional specification of a fraction (to
! make non-integer timesteps) now acts as the true timestep.
! In share/set_timekeeping.F the integer(s) are converted to a real
! number and put back in dt anyway!
! We will deal with the case of the integer variables in
! share/set_timekeeping.F itself.  For now, since they left dt in
! the namelist definition, I will leave this here just in case ...
      model_config_rec%dt    = dt    * P2SI
! All of the following variables are told to be input in *MINUTES*
! These values are converted to units of timesteps in the various
! init routines in phys/module_physics_init.F by dividing by the
! formula STEP = (xxDT*60./dt).  So it seems safe to multiply them
! by P2SI here (with the exception of adding roundoff error later).
! See notes in phys/module_radiation_driver for the radt example.
      model_config_rec%radt  = radt  * P2SI
      model_config_rec%bldt  = bldt  * P2SI
      model_config_rec%cudt  = cudt  * P2SI
      model_config_rec%gsmdt = gsmdt * P2SI
!************************************************************************
#endif

      CLOSE ( UNIT = nml_read_unit , IOSTAT = io_status )

      IF ( io_status .NE. 0 ) THEN
        CALL WRF_ERROR_FATAL ( 'ERROR CLOSING namelist.input' )
      ENDIF

#ifndef NO_NAMELIST_PRINT
      CLOSE ( UNIT = nml_write_unit , IOSTAT = io_status )

      IF ( io_status .NE. 0 ) THEN
        CALL WRF_ERROR_FATAL ( 'ERROR CLOSING namelist.output' )
      ENDIF
#endif

      RETURN

   END SUBROUTINE initial_config

#if 1

   SUBROUTINE  get_config_as_buffer (docs)  ( buffer, buflen, ncopied ) 16,2
! note that model_config_rec_type must be defined as a sequence derived type
      INTEGER,   INTENT(INOUT) ::  buffer(*)
      INTEGER,   INTENT(IN)    ::  buflen
      INTEGER,   INTENT(OUT)   ::  ncopied
!      TYPE(model_config_rec_type) :: model_config_rec
      INTEGER :: nbytes
      CALL wrf_num_bytes_between ( model_config_rec%last_item_in_struct ,   &
                                   model_config_rec%first_item_in_struct ,  &
                                   nbytes )
!      nbytes = loc(model_config_rec%last_item_in_struct) - &
!               loc(model_config_rec%first_item_in_struct)
      IF ( nbytes .gt. buflen ) THEN
        CALL wrf_error_fatal( &
        "get_config_rec_as_buffer: buffer size too small for config_rec" )
      ENDIF
      CALL wrf_mem_copy( model_config_rec, buffer, nbytes )
      ncopied = nbytes
      RETURN
   END SUBROUTINE get_config_as_buffer


   SUBROUTINE  set_config_as_buffer (docs)  ( buffer, buflen ) 16,2
! note that model_config_rec_type must be defined as a sequence derived type
      INTEGER,   INTENT(INOUT) ::  buffer(*)
      INTEGER,   INTENT(IN)    ::  buflen
!      TYPE(model_config_rec_type) :: model_config_rec
      INTEGER :: nbytes
      CALL wrf_num_bytes_between ( model_config_rec%last_item_in_struct ,  &
                                   model_config_rec%first_item_in_struct , &
                                   nbytes )
!      nbytes = loc(model_config_rec%last_item_in_struct) - &
!               loc(model_config_rec%first_item_in_struct)
      IF ( nbytes .gt. buflen ) THEN
        CALL wrf_error_fatal( &
        "set_config_rec_as_buffer: buffer length too small to fill model config record" )
      ENDIF
      CALL wrf_mem_copy( buffer, model_config_rec, nbytes )
      RETURN
   END SUBROUTINE set_config_as_buffer
#else

   SUBROUTINE  get_config_as_buffer (docs)  ( buffer, buflen, ncopied ) 16,2
! note that model_config_rec_type must be defined as a sequence derived type
      INTEGER*1, INTENT(INOUT) ::  buffer(*)
      INTEGER,   INTENT(IN)    ::  buflen
      INTEGER,   INTENT(OUT)   ::  ncopied
!      TYPE(model_config_rec_type) :: model_config_rec
      INTEGER :: nbytes
      nbytes = loc(model_config_rec%last_item_in_struct) - &
               loc(model_config_rec%first_item_in_struct)
      IF ( nbytes .gt. buflen ) THEN
        CALL wrf_error_fatal( &
        "get_config_rec_as_buffer: buffer size too small for config_rec" )
      ENDIF
      CALL wrf_mem_copy( model_config_rec, buffer, nbytes )
      ncopied = nbytes
      RETURN
   END SUBROUTINE get_config_as_buffer


   SUBROUTINE  set_config_as_buffer (docs)  ( buffer, buflen ) 16,2
! note that model_config_rec_type must be defined as a sequence derived type
      INTEGER*1, INTENT(INOUT) ::  buffer(*)
      INTEGER,   INTENT(IN)    ::  buflen
!      TYPE(model_config_rec_type) :: model_config_rec
      INTEGER :: nbytes
      nbytes = loc(model_config_rec%last_item_in_struct) - &
               loc(model_config_rec%first_item_in_struct)
      IF ( nbytes .gt. buflen ) THEN
        CALL wrf_error_fatal( &
        "set_config_rec_as_buffer: buffer length too small to fill model config record" )
      ENDIF
      CALL wrf_mem_copy( buffer, model_config_rec, nbytes )
      RETURN
   END SUBROUTINE set_config_as_buffer
#endif


   SUBROUTINE  model_to_grid_config_rec (docs)   ( id_id , model_config_rec , grid_config_rec ) 75
      INTEGER , INTENT(IN)                         ::  id_id
      TYPE ( model_config_rec_type ) , INTENT(IN)  ::  model_config_rec
      TYPE ( grid_config_rec_type  ) , INTENT(OUT) ::  grid_config_rec
! <DESCRIPTION>
! This routine is called to populate a domain specific configuration
! record of TYPE(grid_config_rec_type) with the configuration information
! for that domain that is stored in TYPE(model_config_rec). Both types
! are defined in frame/module_configure.F.  The input argument is the
! record of type model_config_rec_type contains the model-wide
! configuration information (that is, settings that apply to the model in
! general) and configuration information for each individual domain.  The
! output argument is the record of type grid_config_rec_type which
! contains the model-wide configuration information and the
! domain-specific information for this domain only.  In the
! model_config_rec, the domain specific information is arrays, indexed by
! the grid id's.  In the grid_config_rec the domain-specific information
! is scalar and for the specific domain.  The first argument to this
! routine is the grid id (top-most domain is always 1) as specified in
! the domain-specific namelist variable grid_id.
!
! The actual assignments form the model_config_rec_type to the
! grid_config_rec_type are generate from the rconfig entries in the
! Registry file and included by this routine from the file
! inc/config_assigns.inc.
!
!NOTE: generated subroutines from Registry file rconfig entries are renamed nl_
! instead of rconfig_ due to length limits for subroutine names.
!
!
! </DESCRIPTION>
#undef SOURCE_RECORD
#undef SOURCE_REC_DEX
#undef DEST_RECORD
#define SOURCE_RECORD model_config_rec %
#define SOURCE_REC_DEX (id_id)
#define DEST_RECORD   grid_config_rec %
#include <config_assigns.inc>
   END SUBROUTINE model_to_grid_config_rec



   FUNCTION  in_use_for_config (docs)   ( id, vname ) RESULT ( in_use )
     INTEGER, INTENT(IN) :: id
     CHARACTER*(*), INTENT(IN) :: vname
     LOGICAL in_use
     INTEGER uses

     uses = 0
     in_use = .TRUE.

#  include <in_use_for_config.inc>

     RETURN
   END FUNCTION


! Include the definitions of all the routines that return a namelist values
! back to the driver. These are generated by the registry


   SUBROUTINE  init_module_configure (docs)   1,2
     USE module_scalar_tables
     IMPLICIT NONE
     CALL init_module_scalar_tables
   END SUBROUTINE init_module_configure


   SUBROUTINE  wrf_alt_nml_dynamics (docs)   (nml_read_unit, nml_name) 1,2
!
!<DESCRIPTION>
! If there is an error reading the DYNAMICS namelist, this routine is
! called to check for namelist variables that have been removed by the 
! developers and are still in user's namelists.
!</DESCRIPTION>
!
     IMPLICIT NONE
     INTEGER, INTENT(IN)       :: nml_read_unit
     CHARACTER*(*), INTENT(IN) :: nml_name
     INTEGER                   :: nml_error

#include <namelist_defines.inc>
#include <namelist_statements.inc>

! These are the variables that have been removed
     logical , DIMENSION(max_domains) :: pd_moist
     logical , DIMENSION(max_domains) :: pd_chem
     logical , DIMENSION(max_domains) :: pd_tke
     logical , DIMENSION(max_domains) :: pd_scalar
     NAMELIST /dynamics/ pd_moist
     NAMELIST /dynamics/ pd_chem
     NAMELIST /dynamics/ pd_tke
     NAMELIST /dynamics/ pd_scalar

! Read the namelist again, if it succeeds after adding the above variables,
! it probably failed these are still in the namelist.  If it fails again, we
! will return.

     REWIND ( UNIT = nml_read_unit )
     READ   ( UNIT = nml_read_unit , NML = dynamics , iostat=nml_error )

     IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
        CALL wrf_debug(0, "Are pd_moist, pd_chem, pd_tke, or pd_scalar still in your "// &
                              TRIM(nml_name)//" namelist?")
        CALL wrf_error_fatal("Replace them with moist_adv_opt, chem_adv_opt, tke_adv_opt"// &
                             " and scalar_adv_opt, respectively.")
     ELSE     ! Still failed
        return
     ENDIF

   END SUBROUTINE wrf_alt_nml_dynamics


   SUBROUTINE  wrf_alt_nml_physics (docs)   (nml_read_unit, nml_name) 1,2
!
!<DESCRIPTION>
! If there is an error reading the PHYSICS namelist, this routine is
! called to check for namelist variables that have been removed by the 
! developers and are still in user's namelists.
!</DESCRIPTION>
!
     IMPLICIT NONE
     INTEGER, INTENT(IN)       :: nml_read_unit
     CHARACTER*(*), INTENT(IN) :: nml_name
     INTEGER                   :: nml_error

#include <namelist_defines.inc>
#include <namelist_statements.inc>

! These are the variables that have been removed
     integer , DIMENSION(max_domains) :: ucmcall
     NAMELIST /physics/ ucmcall

! Read the namelist again, if it succeeds after adding the above variables,
! it probably failed these are still in the namelist.  If it fails again, we
! will return.

     REWIND ( UNIT = nml_read_unit )
     READ   ( UNIT = nml_read_unit , NML = physics , iostat=nml_error )

     IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
        CALL wrf_debug(0,"Is ucmcall still in your "// TRIM(nml_name)//" namelist?")
        CALL wrf_error_fatal("Replace it with sf_urban_physics")
     ELSE     ! Still failed
        return
     ENDIF

   END SUBROUTINE wrf_alt_nml_physics


   SUBROUTINE  wrf_alt_nml_fdda (docs)   (nml_read_unit, nml_name) 1,2
!
!<DESCRIPTION>
! If there is an error reading the FDDA namelist, this routine is
! called to check for namelist variables that have been removed by the 
! developers and are still in user's namelists.
!</DESCRIPTION>
!
     IMPLICIT NONE
     INTEGER, INTENT(IN)       :: nml_read_unit
     CHARACTER*(*), INTENT(IN) :: nml_name
     INTEGER                   :: nml_error

#include <namelist_defines.inc>
#include <namelist_statements.inc>

! These are the variables that have been removed
     integer , DIMENSION(max_domains) :: obs_nobs_prt
     NAMELIST /fdda/ obs_nobs_prt

! Read the namelist again, if it succeeds after adding the above variables,
! it probably failed these are still in the namelist.  If it fails again, we
! will return.

     REWIND ( UNIT = nml_read_unit )
     READ   ( UNIT = nml_read_unit , NML = fdda , iostat=nml_error )

     IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
        CALL wrf_debug(0,"Is obs_nobs_prt still in your "// TRIM(nml_name)//" namelist?")
        CALL wrf_error_fatal("Replace it with obs_prt_max")
     ELSE     ! Still failed
        return
     ENDIF

   END SUBROUTINE wrf_alt_nml_fdda


   SUBROUTINE  wrfvar_alt_nml_wrfvar1 (docs)   (nml_read_unit, nml_name) 1,2
!
!<DESCRIPTION>
! If there is an error reading the wrfvar1 namelist, this routine is
! called to check for namelist variables that have been removed by the 
! developers and are still in user's namelists.
!</DESCRIPTION>
!
     IMPLICIT NONE
     INTEGER, INTENT(IN)       :: nml_read_unit
     CHARACTER*(*), INTENT(IN) :: nml_name
     INTEGER                   :: nml_error

#include <namelist_defines.inc>
#include <namelist_statements.inc>

! These are the variables that have been removed
     LOGICAL :: global
     LOGICAL :: print_detail_airep
     LOGICAL :: print_detail_timing
     NAMELIST /wrfvar1/ global
     NAMELIST /wrfvar1/ print_detail_airep
     NAMELIST /wrfvar1/ print_detail_timing

! Read the namelist again, if it succeeds after adding the above variables,
! it probably failed these are still in the namelist.  If it fails again, we
! will return.

     REWIND ( UNIT = nml_read_unit )
     READ   ( UNIT = nml_read_unit , NML = wrfvar1 , iostat=nml_error )

     IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
        CALL wrf_debug(0,"Are global, print_detail_airep, print_detail_timing still in your "// &
                         TRIM(nml_name)//" namelist?")
        CALL wrf_error_fatal("Remove global, print_detail_airep, print_detail_timing "// &
                             "from wrfvar1 namelist as they are obsolete.")
     ELSE     ! Still failed
        return
     ENDIF

   END SUBROUTINE wrfvar_alt_nml_wrfvar1


   SUBROUTINE  wrfvar_alt_nml_wrfvar2 (docs)   (nml_read_unit, nml_name) 1,2
!
!<DESCRIPTION>
! If there is an error reading the wrfvar2 namelist, this routine is
! called to check for namelist variables that have been removed by the 
! developers and are still in user's namelists.
!</DESCRIPTION>
!
     IMPLICIT NONE
     INTEGER, INTENT(IN)       :: nml_read_unit
     CHARACTER*(*), INTENT(IN) :: nml_name
     INTEGER                   :: nml_error

#include <namelist_defines.inc>
#include <namelist_statements.inc>

! These are the variables that have been removed
     LOGICAL :: write_qcw
     LOGICAL :: write_qrn
     LOGICAL :: write_qci
     LOGICAL :: write_qsn
     LOGICAL :: write_qgr
     LOGICAL :: write_filtered_obs
     NAMELIST /wrfvar2/ write_qcw
     NAMELIST /wrfvar2/ write_qrn
     NAMELIST /wrfvar2/ write_qci
     NAMELIST /wrfvar2/ write_qsn
     NAMELIST /wrfvar2/ write_qgr
     NAMELIST /wrfvar2/ write_filtered_obs

! Read the namelist again, if it succeeds after adding the above variables,
! it probably failed these are still in the namelist.  If it fails again, we
! will return.

     REWIND ( UNIT = nml_read_unit )
     READ   ( UNIT = nml_read_unit , NML = wrfvar2 , iostat=nml_error )

     IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
        CALL wrf_debug(0,"Are write_qcw, write_qrn, write_qci, write_qsn, write_qgr, "// &
                         "write_filtered_obs still in your "// &
                         TRIM(nml_name)//" namelist?")
        CALL wrf_error_fatal("Remove write_qcw, write_qrn, write_qci, write_qsn, write_qgr, "// &
                             "write_filtered_obs as they are obsolete.")
     ELSE     ! Still failed
        return
     ENDIF

   END SUBROUTINE wrfvar_alt_nml_wrfvar2


   SUBROUTINE  wrfvar_alt_nml_wrfvar4 (docs)   (nml_read_unit, nml_name) 1,2
!
!<DESCRIPTION>
! If there is an error reading the wrfvar4 namelist, this routine is
! called to check for namelist variables that have been removed by the 
! developers and are still in user's namelists.
!</DESCRIPTION>
!
     IMPLICIT NONE
     INTEGER, INTENT(IN)       :: nml_read_unit
     CHARACTER*(*), INTENT(IN) :: nml_name
     INTEGER                   :: nml_error

#include <namelist_defines.inc>
#include <namelist_statements.inc>

! These are the variables that have been removed
     LOGICAL :: use_eos_radobs
     NAMELIST /wrfvar4/ use_eos_radobs

! Read the namelist again, if it succeeds after adding the above variables,
! it probably failed these are still in the namelist.  If it fails again, we
! will return.

     REWIND ( UNIT = nml_read_unit )
     READ   ( UNIT = nml_read_unit , NML = wrfvar4 , iostat=nml_error )

     IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
        CALL wrf_debug(0,"Is use_eos_radobs still in your "// &
                         TRIM(nml_name)//" namelist?")
        CALL wrf_error_fatal("Remove use_eos_radobs as it is obsolete.")
     ELSE     ! Still failed
        return
     ENDIF

   END SUBROUTINE wrfvar_alt_nml_wrfvar4


   SUBROUTINE  wrfvar_alt_nml_wrfvar14 (docs)   (nml_read_unit, nml_name) 1,2
!
!<DESCRIPTION>
! If there is an error reading the wrfvar14 namelist, this routine is
! called to check for namelist variables that have been removed by the 
! developers and are still in user's namelists.
!</DESCRIPTION>
!
     IMPLICIT NONE
     INTEGER, INTENT(IN)       :: nml_read_unit
     CHARACTER*(*), INTENT(IN) :: nml_name
     INTEGER                   :: nml_error

#include <namelist_defines.inc>
#include <namelist_statements.inc>

! These are the variables that have been removed
     LOGICAL             :: use_crtm_kmatrix_fast
     CHARACTER (LEN=256) :: spccoeff_file
     CHARACTER (LEN=256) :: taucoeff_file
     CHARACTER (LEN=256) :: aerosolcoeff_file
     CHARACTER (LEN=256) :: cloudcoeff_file
     CHARACTER (LEN=256) :: emiscoeff_file
     NAMELIST /wrfvar14/ use_crtm_kmatrix_fast
     NAMELIST /wrfvar14/ spccoeff_file
     NAMELIST /wrfvar14/ taucoeff_file
     NAMELIST /wrfvar14/ aerosolcoeff_file
     NAMELIST /wrfvar14/ cloudcoeff_file
     NAMELIST /wrfvar14/ emiscoeff_file

! Read the namelist again, if it succeeds after adding the above variables,
! it probably failed these are still in the namelist.  If it fails again, we
! will return.

     REWIND ( UNIT = nml_read_unit )
     READ   ( UNIT = nml_read_unit , NML = wrfvar14 , iostat=nml_error )

     IF ( nml_error .EQ. 0 ) then    ! Successul, rm variables must be problem
        CALL wrf_debug(0,"Are use_crtm_kmatrix_fast, spccoeff_file, taucoeff_file, "// &
                         "aerosolcoeff_file, cloudcoeff_file, emiscoeff_file still in your "// &
                         TRIM(nml_name)//" namelist?")
        CALL wrf_error_fatal("Remove them as they are obsolete.")
     ELSE     ! Still failed
        return
     ENDIF

   END SUBROUTINE wrfvar_alt_nml_wrfvar14

END MODULE module_configure



SUBROUTINE  set_scalar_indices_from_config (docs)   ( idomain , dummy2, dummy1 ) 31,5
  USE module_driver_constants
  USE module_state_description
  USE module_wrf_error
  USE module_configure, ONLY : model_config_rec
  USE module_scalar_tables
  IMPLICIT NONE
  INTEGER , INTENT(IN)  :: idomain
  INTEGER               :: dummy1
  INTEGER               :: dummy2

!<DESCRIPTION>
!This routine is called to adjust the integer variables that are defined
!in frame/module_state_description.F (Registry-generated) and that serve
!as indices into 4D tracer arrays for moisture, chemistry, etc.
!Different domains (different grid data structures) are allowed to have
!different sets of tracers so these indices can vary from domain to
!domain. However, since the indices are defined globally in
!module_state_description (a shortcoming in the current software), it is
!necessary that these indices be reset each time a different grid is to
!be computed on.
!
!The scalar idices are set according to the particular physics
!packages -- more specifically in the case of the moisture tracers, microphysics
!packages -- that are stored for each domain in model_config_rec and
!indexed by the grid id, passed in as an argument to this routine.  (The
!initial_config() routine in module_configure is what reads the
!namelist.input file and sets model_config_rec.)
!
!The actual code for calculating the scalar indices on a particular
!domain is generated from the Registry state array definitions for the
!4d tracers and from the package definitions that indicate which physics
!packages use which tracers.
!
!</DESCRIPTION>

#include <scalar_indices.inc>
#include <scalar_indices_init.inc>
  RETURN
END SUBROUTINE set_scalar_indices_from_config