convert_em.F

References to this file elsewhere.
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.
6 
7 
8 PROGRAM convert_data
9 
10    USE module_machine
11    USE module_domain
12    USE module_io_domain
13    USE module_driver_constants
14    USE module_configure
15    USE module_timing
16 #ifdef WRF_CHEM
17    USE module_input_chem_data
18    USE module_input_chem_bioemiss
19 #endif
20    USE module_utility
21 #ifdef DM_PARALLEL
22    USE module_dm
23 #endif
24 
25    IMPLICIT NONE
26 
27 #ifdef WRF_CHEM
28   ! interface
29    INTERFACE
30      ! mediation-supplied 
31      SUBROUTINE med_read_wrf_chem_bioemiss ( grid , config_flags)
32        USE module_domain
33        TYPE (domain) grid
34        TYPE (grid_config_rec_type) config_flags
35      END SUBROUTINE med_read_wrf_chem_bioemiss
36    END INTERFACE
37 #endif
38 
39    REAL    :: time , bdyfrq
40 
41    INTEGER :: debug_level, fid, ierr
42    CHARACTER*256 :: timestr, inpname
43 
44 
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
49 
50    INTEGER :: max_dom, domain_id
51    INTEGER :: idum1, idum2 
52 #ifdef DM_PARALLEL
53    INTEGER                 :: nbytes
54    INTEGER, PARAMETER      :: configbuflen = 4* CONFIG_BUF_LEN
55    INTEGER                 :: configbuf( configbuflen )
56    LOGICAL , EXTERNAL      :: wrf_dm_on_monitor
57 #endif
58 
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
64 
65    CHARACTER (LEN=80)     :: message
66 
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
71 real::t1,t2
72    INTERFACE
73      SUBROUTINE Setup_Timekeeping( grid )
74       USE module_domain
75       TYPE(domain), POINTER :: grid
76      END SUBROUTINE Setup_Timekeeping
77    END INTERFACE
78 
79    !  Define the name of this program (program_name defined in module_domain)
80 
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)
83 
84    program_name = "CONVERT V2.1 "
85 
86 #ifdef DM_PARALLEL
87    CALL disable_quilting
88 #endif
89 
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.
94 
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    CALL WRFU_Initialize( defaultCalendar=WRFU_CAL_GREGORIAN, rc=rc )
98    CALL init_modules(2)   ! Phase 2 resumes after MPI_INIT() (if it is called)
99 
100    !  The configuration switches mostly come from the NAMELIST input.
101 
102 #ifdef DM_PARALLEL
103    IF ( wrf_dm_on_monitor() ) THEN
104       CALL initial_config
105    ENDIF
106    CALL get_config_as_buffer( configbuf, configbuflen, nbytes )
107    CALL wrf_dm_bcast_bytes( configbuf, nbytes )
108    CALL set_config_as_buffer( configbuf, configbuflen )
109    CALL wrf_dm_initialize
110 #else
111    CALL initial_config
112 #endif
113 
114    CALL nl_get_debug_level ( 1, debug_level )
115    CALL set_wrf_debug_level ( debug_level )
116 
117    CALL wrf_message ( program_name )
118 
119    !  Allocate the space for the mother of all domains.
120 
121    NULLIFY( null_domain )
122    CALL wrf_debug ( 100 , 'convert_em: calling alloc_and_configure_domain ' )
123    CALL alloc_and_configure_domain ( domain_id  = 1           , &
124                                      grid       = head_grid   , &
125                                      parent     = null_domain , &
126                                      kid        = -1            )
127 
128    grid => head_grid
129 
130    CALL Setup_Timekeeping ( grid )
131 
132 
133    CALL wrf_debug ( 100 , 'convert_em: calling set_scalar_indices_from_config ' )
134    CALL set_scalar_indices_from_config ( grid%id , idum1, idum2 )
135 
136    CALL wrf_debug ( 100 , 'convert_em: calling model_to_grid_config_rec ' )
137    CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
138 
139    !  Initialize the WRF IO: open files, init file handles, etc.
140 
141    CALL wrf_debug ( 100 , 'convert_em: calling init_wrfio' )
142    CALL init_wrfio
143 
144 #ifdef DM_PARALLEL
145    CALL wrf_debug ( 100 , 'convert_em: re-broadcast the configuration records' )
146    CALL get_config_as_buffer( configbuf, configbuflen, nbytes )
147    CALL wrf_dm_bcast_bytes( configbuf, nbytes )
148    CALL set_config_as_buffer( configbuf, configbuflen )
149 #endif
150 
151    CALL domain_clock_get( grid, current_timestr=timestr )
152    CALL construct_filename2a ( inpname , config_flags%input_inname , grid%id , 2 , timestr )
153    CALL open_r_dataset ( fid, TRIM(inpname) , grid , config_flags , "DATASET=INPUT", ierr )
154    CALL input_model_input      ( fid ,  grid , config_flags , ierr )
155 
156    CALL med_hist_out ( head_grid , 0, config_flags )
157 
158    CALL wrf_shutdown
159 
160    CALL WRFU_Finalize( rc=rc )
161 
162 END PROGRAM convert_data
163