1 !This is a data converter program. Its actions are controlled by
2 !the registry and the namelist. It will read variables on the
3 !'i' stream output and output variables on the 'o' stream as
4 !indicated in the registry. The input and output forms are
5 !controlled by io_form_input and io_form_history in the namelist.input.
13 USE module_driver_constants
17 USE module_input_chem_data
18 USE module_input_chem_bioemiss
31 SUBROUTINE med_read_wrf_chem_bioemiss ( grid , config_flags)
34 TYPE (grid_config_rec_type) config_flags
35 END SUBROUTINE med_read_wrf_chem_bioemiss
41 INTEGER :: debug_level, fid, ierr
42 CHARACTER*256 :: timestr, inpname
45 TYPE(domain) , POINTER :: null_domain
46 TYPE(domain) , POINTER :: grid
47 TYPE (grid_config_rec_type) :: config_flags
48 INTEGER :: number_at_same_level
50 INTEGER :: max_dom, domain_id
51 INTEGER :: idum1, idum2
54 INTEGER, PARAMETER :: configbuflen = 4* CONFIG_BUF_LEN
55 INTEGER :: configbuf( configbuflen )
56 LOGICAL , EXTERNAL :: wrf_dm_on_monitor
59 INTEGER :: ids , ide , jds , jde , kds , kde
60 INTEGER :: ims , ime , jms , jme , kms , kme
61 INTEGER :: ips , ipe , jps , jpe , kps , kpe
62 INTEGER :: ijds , ijde , spec_bdy_width
63 INTEGER :: i , j , k , idts, rc
65 CHARACTER (LEN=80) :: message
67 INTEGER :: start_year , start_month , start_day , start_hour , start_minute , start_second
68 INTEGER :: end_year , end_month , end_day , end_hour , end_minute , end_second
69 INTEGER :: interval_seconds , real_data_init_type
70 INTEGER :: time_loop_max , time_loop
73 SUBROUTINE Setup_Timekeeping( grid )
75 TYPE(domain), POINTER :: grid
76 END SUBROUTINE Setup_Timekeeping
79 ! Define the name of this program (program_name defined in module_domain)
81 ! NOTE: share/input_wrf.F tests first 7 chars of this name to decide
82 ! whether to read P_TOP as metadata from the SI (yes, if .eq. REAL_EM)
84 program_name = "CONVERT V2.1 "
90 ! Initialize the modules used by the WRF system. Many of the CALLs made from the
91 ! init_modules routine are NO-OPs. Typical initializations are: the size of a
92 ! REAL, setting the file handles to a pre-use value, defining moisture and
93 ! chemistry indices, etc.
95 CALL wrf_debug ( 100 , 'convert_em: calling init_modules ' )
96 CALL init_modules(1) ! Phase 1 returns after MPI_INIT() (if it is called)
97 #ifdef NO_LEAP_CALENDAR
98 CALL WRFU_Initialize( defaultCalKind=WRFU_CAL_NOLEAP, rc=rc )
100 CALL WRFU_Initialize( defaultCalKind=WRFU_CAL_GREGORIAN, rc=rc )
102 CALL init_modules(2) ! Phase 2 resumes after MPI_INIT() (if it is called)
104 ! The configuration switches mostly come from the NAMELIST input.
107 IF ( wrf_dm_on_monitor() ) THEN
110 CALL get_config_as_buffer( configbuf, configbuflen, nbytes )
111 CALL wrf_dm_bcast_bytes( configbuf, nbytes )
112 CALL set_config_as_buffer( configbuf, configbuflen )
113 CALL wrf_dm_initialize
118 CALL nl_get_debug_level ( 1, debug_level )
119 CALL set_wrf_debug_level ( debug_level )
121 CALL wrf_message ( program_name )
123 ! Allocate the space for the mother of all domains.
125 NULLIFY( null_domain )
126 CALL wrf_debug ( 100 , 'convert_em: calling alloc_and_configure_domain ' )
127 CALL alloc_and_configure_domain ( domain_id = 1 , &
129 parent = null_domain , &
134 CALL Setup_Timekeeping ( grid )
137 CALL wrf_debug ( 100 , 'convert_em: calling set_scalar_indices_from_config ' )
138 CALL set_scalar_indices_from_config ( grid%id , idum1, idum2 )
140 CALL wrf_debug ( 100 , 'convert_em: calling model_to_grid_config_rec ' )
141 CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
143 ! Initialize the WRF IO: open files, init file handles, etc.
145 CALL wrf_debug ( 100 , 'convert_em: calling init_wrfio' )
149 CALL wrf_debug ( 100 , 'convert_em: re-broadcast the configuration records' )
150 CALL get_config_as_buffer( configbuf, configbuflen, nbytes )
151 CALL wrf_dm_bcast_bytes( configbuf, nbytes )
152 CALL set_config_as_buffer( configbuf, configbuflen )
155 CALL domain_clock_get( grid, current_timestr=timestr )
156 CALL construct_filename2a ( inpname , config_flags%input_inname , grid%id , 2 , timestr )
157 CALL open_r_dataset ( fid, TRIM(inpname) , grid , config_flags , "DATASET=INPUT", ierr )
158 CALL input_model_input ( fid , grid , config_flags , ierr )
160 CALL med_hist_out ( head_grid , 0, config_flags )
164 CALL WRFU_Finalize( rc=rc )
166 END PROGRAM convert_data