Update version number to 4.1
[WPS.git] / metgrid / src / input_module.F
blob9c74d2b08c587eba771dfaedb93da7aae8ed109c
1 module input_module
3    use gridinfo_module
4    use misc_definitions_module
5    use module_debug
6 #ifdef IO_BINARY
7    use module_internal_header_util
8 #endif
9    use parallel_module
10    use queue_module
12    type (queue) :: unit_desc
14    ! WRF I/O API related variables
15    integer :: handle
17    integer :: num_calls
19    character (len=1) :: internal_gridtype
21    contains
24    subroutine input_init(nest_number, istatus)
26       implicit none
27   
28       ! Arguments
29       integer, intent(in) :: nest_number
30       integer, intent(out) :: istatus
31   
32 #include "wrf_io_flags.h"
33 #include "wrf_status_codes.h"
34   
35       ! Local variables
36       integer :: i
37       integer :: comm_1, comm_2
38       character (len=MAX_FILENAME_LEN) :: input_fname
39   
40       istatus = 0
41   
42       if (my_proc_id == IO_NODE .or. do_tiled_input) then
43   
44 #ifdef IO_BINARY
45          if (io_form_input == BINARY) call ext_int_ioinit('sysdep info', istatus)
46 #endif
47 #ifdef IO_NETCDF
48          if (io_form_input == NETCDF) call ext_ncd_ioinit('sysdep info', istatus)
49 #endif
50 #ifdef IO_GRIB1
51          if (io_form_input == GRIB1) call ext_gr1_ioinit('sysdep info', istatus)
52 #endif
53          call mprintf((istatus /= 0),ERROR,'Error in ext_pkg_ioinit')
54      
55          comm_1 = 1
56          comm_2 = 1
57          input_fname = ' '
58          if (gridtype == 'C') then
59 #ifdef IO_BINARY
60             if (io_form_input == BINARY) input_fname = trim(opt_output_from_geogrid_path)//'geo_em.d  .int'
61 #endif
62 #ifdef IO_NETCDF
63             if (io_form_input == NETCDF) input_fname = trim(opt_output_from_geogrid_path)//'geo_em.d  .nc'
64 #endif
65 #ifdef IO_GRIB1
66             if (io_form_input == GRIB1) input_fname = trim(opt_output_from_geogrid_path)//'geo_em.d  .grib'
67 #endif
68             i = len_trim(opt_output_from_geogrid_path)
69             write(input_fname(i+9:i+10),'(i2.2)') nest_number
70          else if (gridtype == 'E') then
71 #ifdef IO_BINARY
72             if (io_form_input == BINARY) input_fname = trim(opt_output_from_geogrid_path)//'geo_nmm.d  .int'
73 #endif
74 #ifdef IO_NETCDF
75             if (io_form_input == NETCDF) input_fname = trim(opt_output_from_geogrid_path)//'geo_nmm.d  .nc'
76 #endif
77 #ifdef IO_GRIB1
78             if (io_form_input == GRIB1) input_fname = trim(opt_output_from_geogrid_path)//'geo_nmm.d  .grib'
79 #endif
80             i = len_trim(opt_output_from_geogrid_path)
81             write(input_fname(i+10:i+11),'(i2.2)') nest_number
82          end if
84          if (nprocs > 1 .and. do_tiled_input) then
85             write(input_fname(len_trim(input_fname)+1:len_trim(input_fname)+5), '(a1,i4.4)') &
86                             '_', my_proc_id
87          end if
88      
89          istatus = 0
90 #ifdef IO_BINARY
91          if (io_form_input == BINARY) &
92             call ext_int_open_for_read(trim(input_fname), comm_1, comm_2, 'sysdep info', handle, istatus)
93 #endif
94 #ifdef IO_NETCDF
95          if (io_form_input == NETCDF) &
96             call ext_ncd_open_for_read(trim(input_fname), comm_1, comm_2, 'sysdep info', handle, istatus)
97 #endif
98 #ifdef IO_GRIB1
99          if (io_form_input == GRIB1) &
100             call ext_gr1_open_for_read(trim(input_fname), comm_1, comm_2, 'sysdep info', handle, istatus)
101 #endif
102          call mprintf((istatus /= 0),ERROR,'Couldn''t open file %s for input.',s1=input_fname)
103      
104          call q_init(unit_desc)
105   
106       end if ! (my_proc_id == IO_NODE .or. do_tiled_input)
107   
108       num_calls = 0
110    end subroutine input_init
113    subroutine read_next_field(start_patch_i, end_patch_i, &
114                               start_patch_j, end_patch_j, &
115                               start_patch_k, end_patch_k, &
116                               cname, cunits, cdesc, memorder, stagger, &
117                               dimnames, sr_x, sr_y, real_array, istatus)
119       implicit none
120   
121       ! Arguments
122       integer, intent(out) :: start_patch_i, end_patch_i, &
123                               start_patch_j, end_patch_j, &
124                               start_patch_k, end_patch_k, &
125                               sr_x, sr_y
126       real, pointer, dimension(:,:,:) :: real_array
127       character (len=*), intent(out) :: cname, memorder, stagger, cunits, cdesc
128       character (len=128), dimension(3), intent(inout) :: dimnames
129       integer, intent(inout) :: istatus
130   
131 #include "wrf_io_flags.h"
132 #include "wrf_status_codes.h"
133   
134       ! Local variables
135       integer :: ndim, wrftype
136       integer :: sm1, em1, sm2, em2, sm3, em3, sp1, ep1, sp2, ep2, sp3, ep3
137       integer, dimension(3) :: domain_start, domain_end, temp
138       real, pointer, dimension(:,:,:) :: real_domain
139       character (len=20) :: datestr
140       type (q_data) :: qd
141   
142       if (my_proc_id == IO_NODE .or. do_tiled_input) then
143   
144          if (num_calls == 0) then
145 #ifdef IO_BINARY
146             if (io_form_input == BINARY) call ext_int_get_next_time(handle, datestr, istatus)
147 #endif
148 #ifdef IO_NETCDF
149             if (io_form_input == NETCDF) call ext_ncd_get_next_time(handle, datestr, istatus)
150 #endif
151 #ifdef IO_GRIB1
152             if (io_form_input == GRIB1) call ext_gr1_get_next_time(handle, datestr, istatus)
153 #endif
154          end if
155      
156          num_calls = num_calls + 1
157    
158 #ifdef IO_BINARY
159          if (io_form_input == BINARY) call ext_int_get_next_var(handle, cname, istatus) 
160 #endif
161 #ifdef IO_NETCDF
162          if (io_form_input == NETCDF) call ext_ncd_get_next_var(handle, cname, istatus) 
163 #endif
164 #ifdef IO_GRIB1
165          if (io_form_input == GRIB1) call ext_gr1_get_next_var(handle, cname, istatus) 
166 #endif
167       end if
168   
169       if (nprocs > 1 .and. .not. do_tiled_input) call parallel_bcast_int(istatus)
170       if (istatus /= 0) return
171   
172       if (my_proc_id == IO_NODE .or. do_tiled_input) then
173   
174          istatus = 0
175 #ifdef IO_BINARY
176          if (io_form_input == BINARY) then
177             call ext_int_get_var_info(handle, cname, ndim, memorder, stagger, domain_start, domain_end, wrftype, istatus)
178          end if
179 #endif
180 #ifdef IO_NETCDF
181          if (io_form_input == NETCDF) then
182             call ext_ncd_get_var_info(handle, cname, ndim, memorder, stagger, domain_start, domain_end, wrftype, istatus)
183             call ext_ncd_get_var_ti_integer(handle, 'sr_x', &
184                                             trim(cname), temp(1), 1, temp(3), istatus)
185             call ext_ncd_get_var_ti_integer(handle, 'sr_y', &
186                                             trim(cname), temp(2), 1, temp(3), istatus)
187          end if
188 #endif
189 #ifdef IO_GRIB1
190          if (io_form_input == GRIB1) then
191             call ext_gr1_get_var_info(handle, cname, ndim, memorder, stagger, domain_start, domain_end, wrftype, istatus)
192             call ext_gr1_get_var_ti_integer(handle, 'sr_x', &
193                                             trim(cname), temp(1), 1, temp(3), istatus)
194             call ext_gr1_get_var_ti_integer(handle, 'sr_y', &
195                                             trim(cname), temp(2), 1, temp(3), istatus)
196          end if
197 #endif
198      
199          call mprintf((istatus /= 0),ERROR,'In read_next_field(), problems with ext_pkg_get_var_info()')
201          start_patch_i = domain_start(1) 
202          start_patch_j = domain_start(2) 
203          end_patch_i = domain_end(1)
204          end_patch_j = domain_end(2)
205          if (ndim == 3) then
206             start_patch_k = domain_start(3) 
207             end_patch_k = domain_end(3) 
208          else
209             domain_start(3) = 1
210             domain_end(3) = 1
211             start_patch_k = 1
212             end_patch_k = 1
213          end if
214      
215          nullify(real_domain)
216      
217          allocate(real_domain(start_patch_i:end_patch_i, start_patch_j:end_patch_j, start_patch_k:end_patch_k))
218 #ifdef IO_BINARY
219          if (io_form_input == BINARY) then
220             call ext_int_read_field(handle, '0000-00-00_00:00:00', cname, real_domain, WRF_REAL, &
221                           1, 1, 0, memorder, stagger, &
222                           dimnames, domain_start, domain_end, domain_start, domain_end, &
223                           domain_start, domain_end, istatus)
224          end if
225 #endif
226 #ifdef IO_NETCDF
227          if (io_form_input == NETCDF) then
228             call ext_ncd_read_field(handle, '0000-00-00_00:00:00', cname, real_domain, WRF_REAL, &
229                           1, 1, 0, memorder, stagger, &
230                           dimnames, domain_start, domain_end, domain_start, domain_end, &
231                           domain_start, domain_end, istatus)
232          end if
233 #endif
234 #ifdef IO_GRIB1
235          if (io_form_input == GRIB1) then
236             call ext_gr1_read_field(handle, '0000-00-00_00:00:00', cname, real_domain, WRF_REAL, &
237                           1, 1, 0, memorder, stagger, &
238                           dimnames, domain_start, domain_end, domain_start, domain_end, &
239                           domain_start, domain_end, istatus)
240          end if
241 #endif
242      
243          call mprintf((istatus /= 0),ERROR,'In read_next_field(), got error code %i.', i1=istatus)
245          if (io_form_input == BINARY) then
246             qd = q_remove(unit_desc)
247             cunits = qd%units
248             cdesc = qd%description
249             stagger = qd%stagger
250             sr_x = qd%sr_x
251             sr_y = qd%sr_y
252          else
253             cunits = ' '
254             cdesc = ' '
255             stagger = ' '
256             sr_x = temp(1)
257             sr_y = temp(2)
258         
259 #ifdef IO_NETCDF
260             if (io_form_input == NETCDF) then
261                call ext_ncd_get_var_ti_char(handle, 'units', cname, cunits, istatus)
262                call ext_ncd_get_var_ti_char(handle, 'description', cname, cdesc, istatus)
263                call ext_ncd_get_var_ti_char(handle, 'stagger', cname, stagger, istatus)
264             end if
265 #endif
266 #ifdef IO_GRIB1
267             if (io_form_input == GRIB1) then
268                call ext_gr1_get_var_ti_char(handle, 'units', cname, cunits, istatus)
269                call ext_gr1_get_var_ti_char(handle, 'description', cname, cdesc, istatus)
270                call ext_gr1_get_var_ti_char(handle, 'stagger', cname, stagger, istatus)
271             end if
272 #endif
273          end if
274   
275       end if ! (my_proc_id == IO_NODE .or. do_tiled_input)
277       if (nprocs > 1 .and. .not. do_tiled_input) then
278          call parallel_bcast_char(cname, len(cname))
279          call parallel_bcast_char(cunits, len(cunits))
280          call parallel_bcast_char(cdesc, len(cdesc))
281          call parallel_bcast_char(memorder, len(memorder))
282          call parallel_bcast_char(stagger, len(stagger))
283          call parallel_bcast_char(dimnames(1), 128)
284          call parallel_bcast_char(dimnames(2), 128)
285          call parallel_bcast_char(dimnames(3), 128)
286          call parallel_bcast_int(domain_start(3))
287          call parallel_bcast_int(domain_end(3))
288          call parallel_bcast_int(sr_x)
289          call parallel_bcast_int(sr_y)
290    
291          sp1 = my_minx
292          ep1 = my_maxx - 1
293          sp2 = my_miny
294          ep2 = my_maxy - 1
295          sp3 = domain_start(3)
296          ep3 = domain_end(3)
297    
298          if (internal_gridtype == 'C') then
299             if (my_x /= nproc_x - 1 .or. stagger == 'U' .or. stagger == 'CORNER' .or. sr_x > 1) then
300                ep1 = ep1 + 1
301             end if
302             if (my_y /= nproc_y - 1 .or. stagger == 'V' .or. stagger == 'CORNER' .or. sr_y > 1) then
303                ep2 = ep2 + 1
304             end if
305          else if (internal_gridtype == 'E') then
306             ep1 = ep1 + 1
307             ep2 = ep2 + 1
308          end if
309    
310          if (sr_x > 1) then
311             sp1 = (sp1-1)*sr_x+1
312             ep1 =  ep1   *sr_x
313          end if
314          if (sr_y > 1) then
315             sp2 = (sp2-1)*sr_y+1
316             ep2 =  ep2   *sr_y
317          end if
319          sm1 = sp1
320          em1 = ep1
321          sm2 = sp2
322          em2 = ep2
323          sm3 = sp3
324          em3 = ep3
325    
326          start_patch_i = sp1
327          end_patch_i   = ep1
328          start_patch_j = sp2
329          end_patch_j   = ep2
330          start_patch_k = sp3
331          end_patch_k   = ep3
332    
333          allocate(real_array(sm1:em1,sm2:em2,sm3:em3))
334          if (my_proc_id /= IO_NODE) then
335             allocate(real_domain(1,1,1))
336             domain_start(1) = 1
337             domain_start(2) = 1
338             domain_start(3) = 1
339             domain_end(1) = 1
340             domain_end(2) = 1
341             domain_end(3) = 1
342          end if
343          call scatter_whole_field_r(real_array, &
344                                    sm1, em1, sm2, em2, sm3, em3, &
345                                    sp1, ep1, sp2, ep2, sp3, ep3, &
346                                    real_domain, &
347                                    domain_start(1), domain_end(1), &
348                                    domain_start(2), domain_end(2), &
349                                    domain_start(3), domain_end(3))
350          deallocate(real_domain)
352       else
353   
354          real_array => real_domain
356       end if
358    end subroutine read_next_field
360    subroutine read_global_attrs(title, start_date, grid_type, dyn_opt,                                &
361                                 west_east_dim, south_north_dim, bottom_top_dim,                       &
362                                 we_patch_s, we_patch_e, we_patch_s_stag, we_patch_e_stag,             &
363                                 sn_patch_s, sn_patch_e, sn_patch_s_stag, sn_patch_e_stag,             &
364                                 map_proj, mminlu, num_land_cat, is_water, is_lake, is_ice, is_urban,  &
365                                 isoilwater, grid_id, parent_id, i_parent_start, j_parent_start,       &
366                                 i_parent_end, j_parent_end, dx, dy, cen_lat, moad_cen_lat, cen_lon,   &
367                                 stand_lon, truelat1, truelat2, pole_lat, pole_lon, parent_grid_ratio, &
368                                 corner_lats, corner_lons, sr_x, sr_y)
370       implicit none
371   
372       ! Arguments
373       integer, intent(out) :: dyn_opt, west_east_dim, south_north_dim, bottom_top_dim, map_proj,   &
374                  is_water, is_lake, we_patch_s, we_patch_e, we_patch_s_stag, we_patch_e_stag,      &
375                  sn_patch_s, sn_patch_e, sn_patch_s_stag, sn_patch_e_stag,                         &
376                  is_ice, is_urban, isoilwater, grid_id, parent_id, i_parent_start, j_parent_start, &
377                  i_parent_end, j_parent_end, parent_grid_ratio, sr_x, sr_y, num_land_cat
378       real, intent(out) :: dx, dy, cen_lat, moad_cen_lat, cen_lon, stand_lon, truelat1, truelat2,  &
379                  pole_lat, pole_lon
380       real, dimension(16), intent(out) :: corner_lats, corner_lons
381       character (len=128), intent(out) :: title, start_date, grid_type, mminlu
382   
383       ! Local variables
384       integer :: istatus, i
385       real :: wps_version
386       character (len=128) :: cunits, cdesc, cstagger
387       integer, dimension(3) :: sr
388       type (q_data) :: qd
389   
390       if (my_proc_id == IO_NODE .or. do_tiled_input) then
391   
392 #ifdef IO_BINARY
393          if (io_form_input == BINARY) then
394             istatus = 0
395             do while (istatus == 0) 
396                cunits = ' '
397                cdesc = ' '
398                cstagger = ' '
399                sr = 0
400                call ext_int_get_var_ti_char(handle, 'units', 'VAR', cunits, istatus)
401          
402                if (istatus == 0) then
403                   call ext_int_get_var_ti_char(handle, 'description', 'VAR', cdesc, istatus)
404           
405                   if (istatus == 0) then
406                      call ext_int_get_var_ti_char(handle, 'stagger', 'VAR', cstagger, istatus)
408                     if (istatus == 0) then
409                     call ext_int_get_var_ti_integer(handle, 'sr_x', 'VAR', sr(1), 1, sr(3), istatus)
411                         if (istatus == 0) then
412                         call ext_int_get_var_ti_integer(handle, 'sr_y', 'VAR', sr(2), 1, sr(3), istatus)
413          
414                              qd%units = cunits
415                              qd%description = cdesc
416                              qd%stagger = cstagger
417                              qd%sr_x = sr(1)
418                              qd%sr_y = sr(2)
419                              call q_insert(unit_desc, qd)
421                         end if
422                     end if
423                   end if
424                end if
425             end do
426          end if
427 #endif
428      
429          call ext_get_dom_ti_char          ('TITLE', title)
430          if (index(title,'GEOGRID V4.1') /= 0) then
431             wps_version = 4.1
432          else if (index(title,'GEOGRID V4.0.3') /= 0) then
433             wps_version = 4.03
434          else if (index(title,'GEOGRID V4.0.2') /= 0) then
435             wps_version = 4.02
436          else if (index(title,'GEOGRID V4.0.1') /= 0) then
437             wps_version = 4.01
438          else if (index(title,'GEOGRID V4.0') /= 0) then
439             wps_version = 4.0
440          else if (index(title,'GEOGRID V3.9.1') /= 0) then
441             wps_version = 3.91
442          else if (index(title,'GEOGRID V3.9.0.1') /= 0) then
443             wps_version = 3.901
444          else if (index(title,'GEOGRID V3.9') /= 0) then
445             wps_version = 3.9
446          else if (index(title,'GEOGRID V3.8.1') /= 0) then
447             wps_version = 3.81
448          else if (index(title,'GEOGRID V3.8') /= 0) then
449             wps_version = 3.8
450          else if (index(title,'GEOGRID V3.7.1') /= 0) then
451             wps_version = 3.71
452          else if (index(title,'GEOGRID V3.7') /= 0) then
453             wps_version = 3.7
454          else if (index(title,'GEOGRID V3.6.1') /= 0) then
455             wps_version = 3.61
456          else if (index(title,'GEOGRID V3.6') /= 0) then
457             wps_version = 3.6
458          else if (index(title,'GEOGRID V3.5.1') /= 0) then
459             wps_version = 3.51
460          else if (index(title,'GEOGRID V3.5') /= 0) then
461             wps_version = 3.5
462          else if (index(title,'GEOGRID V3.4.1') /= 0) then
463             wps_version = 3.41
464          else if (index(title,'GEOGRID V3.4') /= 0) then
465             wps_version = 3.4
466          else if (index(title,'GEOGRID V3.3.1') /= 0) then
467             wps_version = 3.31
468          else if (index(title,'GEOGRID V3.3') /= 0) then
469             wps_version = 3.3
470          else if (index(title,'GEOGRID V3.2.1') /= 0) then
471             wps_version = 3.21
472          else if (index(title,'GEOGRID V3.2') /= 0) then
473             wps_version = 3.2
474          else if (index(title,'GEOGRID V3.1.1') /= 0) then
475             wps_version = 3.11
476          else if (index(title,'GEOGRID V3.1') /= 0) then
477             wps_version = 3.1
478          else if (index(title,'GEOGRID V3.0.1') /= 0) then
479             wps_version = 3.01
480          else
481             wps_version = 3.0
482          end if
483          call mprintf(.true.,DEBUG,'Reading static data from WPS version %f', f1=wps_version)
484          call ext_get_dom_ti_char          ('SIMULATION_START_DATE', start_date)
485          call ext_get_dom_ti_integer_scalar('WEST-EAST_GRID_DIMENSION', west_east_dim)
486          call ext_get_dom_ti_integer_scalar('SOUTH-NORTH_GRID_DIMENSION', south_north_dim)
487          call ext_get_dom_ti_integer_scalar('BOTTOM-TOP_GRID_DIMENSION', bottom_top_dim)
488          call ext_get_dom_ti_integer_scalar('WEST-EAST_PATCH_START_UNSTAG', we_patch_s)
489          call ext_get_dom_ti_integer_scalar('WEST-EAST_PATCH_END_UNSTAG', we_patch_e)
490          call ext_get_dom_ti_integer_scalar('WEST-EAST_PATCH_START_STAG', we_patch_s_stag)
491          call ext_get_dom_ti_integer_scalar('WEST-EAST_PATCH_END_STAG', we_patch_e_stag)
492          call ext_get_dom_ti_integer_scalar('SOUTH-NORTH_PATCH_START_UNSTAG', sn_patch_s)
493          call ext_get_dom_ti_integer_scalar('SOUTH-NORTH_PATCH_END_UNSTAG', sn_patch_e)
494          call ext_get_dom_ti_integer_scalar('SOUTH-NORTH_PATCH_START_STAG', sn_patch_s_stag)
495          call ext_get_dom_ti_integer_scalar('SOUTH-NORTH_PATCH_END_STAG', sn_patch_e_stag)
496          call ext_get_dom_ti_char          ('GRIDTYPE', grid_type)
497          call ext_get_dom_ti_real_scalar   ('DX', dx)
498          call ext_get_dom_ti_real_scalar   ('DY', dy)
499          call ext_get_dom_ti_integer_scalar('DYN_OPT', dyn_opt)
500          call ext_get_dom_ti_real_scalar   ('CEN_LAT', cen_lat)
501          call ext_get_dom_ti_real_scalar   ('CEN_LON', cen_lon)
502          call ext_get_dom_ti_real_scalar   ('TRUELAT1', truelat1)
503          call ext_get_dom_ti_real_scalar   ('TRUELAT2', truelat2)
504          call ext_get_dom_ti_real_scalar   ('MOAD_CEN_LAT', moad_cen_lat)
505          call ext_get_dom_ti_real_scalar   ('STAND_LON', stand_lon)
506          call ext_get_dom_ti_real_scalar   ('POLE_LAT', pole_lat)
507          call ext_get_dom_ti_real_scalar   ('POLE_LON', pole_lon)
508          call ext_get_dom_ti_real_vector   ('corner_lats', corner_lats, 16)
509          call ext_get_dom_ti_real_vector   ('corner_lons', corner_lons, 16)
510          call ext_get_dom_ti_integer_scalar('MAP_PROJ', map_proj)
511          call ext_get_dom_ti_char          ('MMINLU', mminlu)
512          if ( wps_version >= 3.01 ) then
513             call ext_get_dom_ti_integer_scalar('NUM_LAND_CAT', num_land_cat)
514          else
515             num_land_cat = 24
516          end if
517          call ext_get_dom_ti_integer_scalar('ISWATER', is_water)
518          if ( wps_version >= 3.01 ) then
519             call ext_get_dom_ti_integer_scalar('ISLAKE', is_lake)
520          else
521             is_lake = -1
522          end if
523          call ext_get_dom_ti_integer_scalar('ISICE', is_ice)
524          call ext_get_dom_ti_integer_scalar('ISURBAN', is_urban)
525          call ext_get_dom_ti_integer_scalar('ISOILWATER', isoilwater)
526          call ext_get_dom_ti_integer_scalar('grid_id', grid_id)
527          call ext_get_dom_ti_integer_scalar('parent_id', parent_id)
528          call ext_get_dom_ti_integer_scalar('i_parent_start', i_parent_start)
529          call ext_get_dom_ti_integer_scalar('j_parent_start', j_parent_start)
530          call ext_get_dom_ti_integer_scalar('i_parent_end', i_parent_end)
531          call ext_get_dom_ti_integer_scalar('j_parent_end', j_parent_end)
532          call ext_get_dom_ti_integer_scalar('parent_grid_ratio', parent_grid_ratio)
533          call ext_get_dom_ti_integer_scalar('sr_x', sr_x)
534          call ext_get_dom_ti_integer_scalar('sr_y', sr_y)
535    
536       end if
538   
539       if (nprocs > 1 .and. .not. do_tiled_input) then
540   
541          call parallel_bcast_char(title, len(title))
542          call parallel_bcast_char(start_date, len(start_date))
543          call parallel_bcast_char(grid_type, len(grid_type))
544          call parallel_bcast_int(west_east_dim)
545          call parallel_bcast_int(south_north_dim)
546          call parallel_bcast_int(bottom_top_dim)
547          call parallel_bcast_int(we_patch_s)
548          call parallel_bcast_int(we_patch_e)
549          call parallel_bcast_int(we_patch_s_stag)
550          call parallel_bcast_int(we_patch_e_stag)
551          call parallel_bcast_int(sn_patch_s)
552          call parallel_bcast_int(sn_patch_e)
553          call parallel_bcast_int(sn_patch_s_stag)
554          call parallel_bcast_int(sn_patch_e_stag)
555          call parallel_bcast_int(sr_x)
556          call parallel_bcast_int(sr_y)
558          ! Must figure out patch dimensions from info in parallel module
559 !         we_patch_s      = my_minx
560 !         we_patch_s_stag = my_minx
561 !         we_patch_e      = my_maxx - 1
562 !         sn_patch_s      = my_miny
563 !         sn_patch_s_stag = my_miny
564 !         sn_patch_e      = my_maxy - 1
566 !         if (trim(grid_type) == 'C') then
567 !            if (my_x /= nproc_x - 1) then
568 !               we_patch_e_stag = we_patch_e + 1
569 !            end if
570 !            if (my_y /= nproc_y - 1) then
571 !               sn_patch_e_stag = sn_patch_e + 1
572 !            end if
573 !         else if (trim(grid_type) == 'E') then
574 !            we_patch_e = we_patch_e + 1
575 !            sn_patch_e = sn_patch_e + 1
576 !            we_patch_e_stag = we_patch_e
577 !            sn_patch_e_stag = sn_patch_e
578 !         end if
580          call parallel_bcast_real(dx)
581          call parallel_bcast_real(dy)
582          call parallel_bcast_int(dyn_opt)
583          call parallel_bcast_real(cen_lat)
584          call parallel_bcast_real(cen_lon)
585          call parallel_bcast_real(truelat1)
586          call parallel_bcast_real(truelat2)
587          call parallel_bcast_real(pole_lat)
588          call parallel_bcast_real(pole_lon)
589          call parallel_bcast_real(moad_cen_lat)
590          call parallel_bcast_real(stand_lon)
591          do i=1,16
592             call parallel_bcast_real(corner_lats(i))
593             call parallel_bcast_real(corner_lons(i))
594          end do
595          call parallel_bcast_int(map_proj)
596          call parallel_bcast_char(mminlu, len(mminlu))
597          call parallel_bcast_int(is_water)
598          call parallel_bcast_int(is_lake)
599          call parallel_bcast_int(is_ice)
600          call parallel_bcast_int(is_urban)
601          call parallel_bcast_int(isoilwater)
602          call parallel_bcast_int(grid_id)
603          call parallel_bcast_int(parent_id)
604          call parallel_bcast_int(i_parent_start)
605          call parallel_bcast_int(i_parent_end)
606          call parallel_bcast_int(j_parent_start)
607          call parallel_bcast_int(j_parent_end)
608          call parallel_bcast_int(parent_grid_ratio)
609       end if
610   
611       internal_gridtype = grid_type
613    end subroutine read_global_attrs
616    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
617    ! Name: ext_get_dom_ti_integer
618    !
619    ! Purpose: Read a domain time-independent integer attribute from input.
620    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
621    subroutine ext_get_dom_ti_integer_scalar(var_name, var_value, suppress_errors)
623       implicit none
625       ! Arguments
626       integer, intent(out) :: var_value
627       character (len=*), intent(in) :: var_name
628       logical, intent(in), optional :: suppress_errors
630       ! Local variables
631       integer :: istatus, outcount
633 #ifdef IO_BINARY
634       if (io_form_input == BINARY) then
635          call ext_int_get_dom_ti_integer(handle, trim(var_name), &
636                                          var_value, &
637                                          1, outcount, istatus)
638       end if
639 #endif
640 #ifdef IO_NETCDF
641       if (io_form_input == NETCDF) then
642          call ext_ncd_get_dom_ti_integer(handle, trim(var_name), &
643                                          var_value, &
644                                          1, outcount, istatus)
645       end if
646 #endif
647 #ifdef IO_GRIB1
648       if (io_form_input == GRIB1) then
649          call ext_gr1_get_dom_ti_integer(handle, trim(var_name), &
650                                          var_value, &
651                                          1, outcount, istatus)
652       end if
653 #endif
655       if (present(suppress_errors)) then
656          call mprintf((istatus /= 0 .and. .not.suppress_errors),ERROR,'Error while reading domain time-independent attribute.')
657       else
658          call mprintf((istatus /= 0),ERROR,'Error while reading domain time-independent attribute.')
659       end if
661    end subroutine ext_get_dom_ti_integer_scalar
664    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
665    ! Name: ext_get_dom_ti_integer
666    !
667    ! Purpose: Read a domain time-independent integer attribute from input.
668    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
669    subroutine ext_get_dom_ti_integer_vector(var_name, var_value, n)
671       implicit none
673       ! Arguments
674       integer, intent(in) :: n
675       integer, dimension(n), intent(out) :: var_value
676       character (len=*), intent(in) :: var_name
678       ! Local variables
679       integer :: istatus, outcount
681 #ifdef IO_BINARY
682       if (io_form_input == BINARY) then
683          call ext_int_get_dom_ti_integer(handle, trim(var_name), &
684                                          var_value, &
685                                          n, outcount, istatus)
686       end if
687 #endif
688 #ifdef IO_NETCDF
689       if (io_form_input == NETCDF) then
690          call ext_ncd_get_dom_ti_integer(handle, trim(var_name), &
691                                          var_value, &
692                                          n, outcount, istatus)
693       end if
694 #endif
695 #ifdef IO_GRIB1
696       if (io_form_input == GRIB1) then
697          call ext_gr1_get_dom_ti_integer(handle, trim(var_name), &
698                                          var_value, &
699                                          n, outcount, istatus)
700       end if
701 #endif
703       call mprintf((istatus /= 0),ERROR,'Error while reading domain time-independent attribute.')
705    end subroutine ext_get_dom_ti_integer_vector
708    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
709    ! Name: ext_get_dom_ti_real
710    !
711    ! Purpose: Read a domain time-independent real attribute from input.
712    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
713    subroutine ext_get_dom_ti_real_scalar(var_name, var_value)
715       implicit none
717       ! Arguments
718       real, intent(out) :: var_value
719       character (len=*), intent(in) :: var_name
721       ! Local variables
722       integer :: istatus, outcount
724 #ifdef IO_BINARY
725       if (io_form_input == BINARY) then
726          call ext_int_get_dom_ti_real(handle, trim(var_name), &
727                                          var_value, &
728                                          1, outcount, istatus)
729       end if
730 #endif
731 #ifdef IO_NETCDF
732       if (io_form_input == NETCDF) then
733          call ext_ncd_get_dom_ti_real(handle, trim(var_name), &
734                                          var_value, &
735                                          1, outcount, istatus)
736       end if
737 #endif
738 #ifdef IO_GRIB1
739       if (io_form_input == GRIB1) then
740          call ext_gr1_get_dom_ti_real(handle, trim(var_name), &
741                                          var_value, &
742                                          1, outcount, istatus)
743       end if
744 #endif
746       call mprintf((istatus /= 0),ERROR,'Error while reading domain time-independent attribute.')
748    end subroutine ext_get_dom_ti_real_scalar
751    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
752    ! Name: ext_get_dom_ti_real
753    !
754    ! Purpose: Read a domain time-independent real attribute from input.
755    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
756    subroutine ext_get_dom_ti_real_vector(var_name, var_value, n)
758       implicit none
760       ! Arguments
761       integer, intent(in) :: n
762       real, dimension(n), intent(out) :: var_value
763       character (len=*), intent(in) :: var_name
765       ! Local variables
766       integer :: istatus, outcount
768 #ifdef IO_BINARY
769       if (io_form_input == BINARY) then
770          call ext_int_get_dom_ti_real(handle, trim(var_name), &
771                                          var_value, &
772                                          n, outcount, istatus)
773       end if
774 #endif
775 #ifdef IO_NETCDF
776       if (io_form_input == NETCDF) then
777          call ext_ncd_get_dom_ti_real(handle, trim(var_name), &
778                                          var_value, &
779                                          n, outcount, istatus)
780       end if
781 #endif
782 #ifdef IO_GRIB1
783       if (io_form_input == GRIB1) then
784          call ext_gr1_get_dom_ti_real(handle, trim(var_name), &
785                                          var_value, &
786                                          n, outcount, istatus)
787       end if
788 #endif
790       call mprintf((istatus /= 0),ERROR,'Error while reading domain time-independent attribute.')
792    end subroutine ext_get_dom_ti_real_vector
795    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
796    ! Name: ext_get_dom_ti_char
797    !
798    ! Purpose: Read a domain time-independent character attribute from input.
799    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
800    subroutine ext_get_dom_ti_char(var_name, var_value)
802       implicit none
804       ! Arguments
805       character (len=*), intent(in) :: var_name
806       character (len=128), intent(out) :: var_value
808       ! Local variables
809       integer :: istatus
811 #ifdef IO_BINARY
812       if (io_form_input == BINARY) then
813          call ext_int_get_dom_ti_char(handle, trim(var_name), &
814                                          var_value, &
815                                          istatus)
816       end if
817 #endif
818 #ifdef IO_NETCDF
819       if (io_form_input == NETCDF) then
820          call ext_ncd_get_dom_ti_char(handle, trim(var_name), &
821                                          var_value, &
822                                          istatus)
823       end if
824 #endif
825 #ifdef IO_GRIB1
826       if (io_form_input == GRIB1) then
827          call ext_gr1_get_dom_ti_char(handle, trim(var_name), &
828                                          var_value, &
829                                          istatus)
830       end if
831 #endif
833       call mprintf((istatus /= 0),ERROR,'Error in reading domain time-independent attribute')
835    end subroutine ext_get_dom_ti_char
838    subroutine input_close()
840       implicit none
841   
842       ! Local variables
843       integer :: istatus
844   
845       istatus = 0
846       if (my_proc_id == IO_NODE .or. do_tiled_input) then
847 #ifdef IO_BINARY
848          if (io_form_input == BINARY) then
849             call ext_int_ioclose(handle, istatus)
850             call ext_int_ioexit(istatus)
851          end if
852 #endif
853 #ifdef IO_NETCDF
854          if (io_form_input == NETCDF) then
855             call ext_ncd_ioclose(handle, istatus)
856             call ext_ncd_ioexit(istatus)
857          end if
858 #endif
859 #ifdef IO_GRIB1
860          if (io_form_input == GRIB1) then
861             call ext_gr1_ioclose(handle, istatus)
862             call ext_gr1_ioexit(istatus)
863          end if
864 #endif
865       end if
867       call q_destroy(unit_desc)
869    end subroutine input_close
871 end module input_module