!WRF:DRIVER_LAYER:CONFIGURATION
!
MODULE module_configure 569
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=4) :: mminlu = ' ' ! character string for landuse table
PRIVATE read_namelist_data
CONTAINS
! Model layer, even though it does I/O -- special case of namelist I/O.
SUBROUTINE initial_config 16,3
IMPLICIT NONE
INTEGER :: io_status, nml_unit
! define as temporaries
#include <namelist_defines.inc>
! Statements that specify the namelists
#include <namelist_statements.inc>
OPEN ( UNIT = 10 , &
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
nml_unit = 10
! Statements that set the namelist vars to default vals
# include <namelist_defaults.inc>
! Statements that read the namelist are in this file
# define NAMELIST_READ_ERROR_LABEL 9200
# include <config_reads.inc>
! 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>
CLOSE ( UNIT = 10 , IOSTAT = io_status )
IF ( io_status .NE. 0 ) THEN
CALL WRF_ERROR_FATAL
( 'ERROR CLOSING namelist.input' )
ENDIF
RETURN
9200 CONTINUE
CALL wrf_error_fatal
( 'module_configure: initial_config: error reading namelist' )
END SUBROUTINE initial_config
#if 1
SUBROUTINE get_config_as_buffer( buffer, buflen, ncopied ) 13,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 to 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( buffer, buflen ) 13,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( buffer, buflen, ncopied ) 13,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 to 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( buffer, buflen ) 13,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 ( id_id , model_config_rec , grid_config_rec ) 28
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
#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
! 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 1
IMPLICIT NONE
! Local vars
INTEGER i , j
DO j = 1, max_domains
#include <scalar_tables_init.inc>
END DO
END SUBROUTINE init_module_configure
END MODULE module_configure
! Special (outside registry)
SUBROUTINE get_mminlu ( retval ) 2,1
USE module_configure
CHARACTER(LEN=4) :: retval
retval(1:4) = mminlu(1:4) ! mminlu is defined in module_configure
RETURN
END SUBROUTINE get_mminlu
SUBROUTINE set_mminlu ( inval ) 10,1
USE module_configure
CHARACTER(LEN=4) :: inval
mminlu(1:4) = inval(1:4) ! mminlu is defined in module_configure
RETURN
END SUBROUTINE set_mminlu
#include <get_nl_config.inc>
SUBROUTINE set_scalar_indices_from_config ( idomain , dummy2, dummy1 ) 21,4
USE module_driver_constants
USE module_state_description
USE module_wrf_error
USE module_configure
IMPLICIT NONE
INTEGER , INTENT(IN) :: idomain
INTEGER :: dummy1
INTEGER :: dummy2
#include <scalar_indices.inc>
#include <scalar_indices_init.inc>
RETURN
END SUBROUTINE set_scalar_indices_from_config