Subtract 1 from the specified e_we and e_sn for NMM domains
[WPS.git] / geogrid / src / gridinfo_module.F90
blobdedb9a0fb43a539b6398cf69b364d66c7494e5e4
1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2 ! MODULE GRIDINFO_MODULE
4 ! This module handles (i.e., acquires, stores, and makes available) all data
5 !   describing the model domains to be processed.
6 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
7 module gridinfo_module
9    use misc_definitions_module
10    use module_debug
12    ! Parameters
13    integer, parameter :: MAX_DOMAINS = 21
15    ! Variables
16    integer :: iproj_type, n_domains, io_form_output, dyn_opt
17    integer, dimension(MAX_DOMAINS) :: parent_grid_ratio, parent_id, ixdim, jydim
18    real :: known_lat, known_lon, stand_lon, truelat1, truelat2, known_x, known_y, &
19            dxkm, dykm, phi, lambda, ref_lat, ref_lon, ref_x, ref_y
20    real, dimension(MAX_DOMAINS) :: parent_ll_x, parent_ll_y, parent_ur_x, parent_ur_y
21    character (len=128) :: geog_data_path, opt_output_from_geogrid_path, opt_geogrid_tbl_path
23    character (len=128), dimension(MAX_DOMAINS) :: geog_data_res 
24    character (len=1) :: gridtype
25    logical :: do_tiled_output
26    integer :: debug_level
28    contains
30    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!  
31    ! Name: get_grid_params
32    !
33    ! Purpose: This subroutine retrieves all parameters regarding the model domains
34    !    to be processed by geogrid.exe. This includes map parameters, domain
35    !    size and location, and nest information. 
36    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!  
37    subroutine get_grid_params()
39       implicit none
40   
41       ! Local variables
42       integer :: i, j, max_dom, funit, io_form_geogrid, interval_seconds
43       real :: dx, dy, rparent_gridpts
44       integer, dimension(MAX_DOMAINS) :: i_parent_start, j_parent_start, &
45                            s_we, e_we, s_sn, e_sn, &
46                            start_year, start_month, start_day, start_hour, start_minute, start_second, &
47                            end_year,   end_month,   end_day,   end_hour,   end_minute,   end_second
48       character (len=128) :: map_proj
49       character (len=128), dimension(MAX_DOMAINS) :: start_date, end_date
50       character (len=3) :: wrf_core
51       logical :: is_used
53       namelist /share/ wrf_core, max_dom, start_date, end_date, &
54                         start_year, end_year, start_month, end_month, &
55                         start_day, end_day, start_hour, end_hour, &
56                         start_minute, end_minute, start_second, end_second, &
57                         interval_seconds, &
58                         io_form_geogrid, opt_output_from_geogrid_path, debug_level
59       namelist /geogrid/ parent_id, parent_grid_ratio, &
60                          i_parent_start, j_parent_start, s_we, e_we, s_sn, e_sn, &
61                          map_proj, ref_x, ref_y, ref_lat, ref_lon, &
62                          truelat1, truelat2, stand_lon, dx, dy, &
63                          geog_data_res, geog_data_path, opt_geogrid_tbl_path
64   
65       ! Set defaults for namelist variables
66       debug_level = 0
67       io_form_geogrid = 2
68       wrf_core = 'ARW'
69       max_dom = 1
70       geog_data_path = 'NOT_SPECIFIED'
71       ref_x = NAN
72       ref_y = NAN
73       ref_lat = NAN
74       ref_lon = NAN
75       dx = 10000.
76       dy = 10000.
77       map_proj = 'Lambert'
78       truelat1 = NAN
79       truelat2 = NAN
80       stand_lon = NAN
81       do i=1,MAX_DOMAINS
82          geog_data_res(i) = 'default'
83          parent_id(i) = 1
84          parent_grid_ratio(i) = INVALID
85          s_we(i) = 1
86          e_we(i) = INVALID
87          s_sn(i) = 1
88          e_sn(i) = INVALID
89          start_year(i) = 0
90          start_month(i) = 0
91          start_day(i) = 0
92          start_hour(i) = 0
93          start_minute(i) = 0
94          start_second(i) = 0
95          end_year(i) = 0
96          end_month(i) = 0
97          end_day(i) = 0
98          end_hour(i) = 0
99          end_minute(i) = 0
100          end_second(i) = 0
101          start_date(i) = '0000-00-00_00:00:00'
102          end_date(i) = '0000-00-00_00:00:00'
103       end do
104       opt_output_from_geogrid_path = './'
105       opt_geogrid_tbl_path = 'geogrid/'
106       interval_seconds = INVALID
107       
108       ! Read parameters from Fortran namelist
109       do funit=10,100
110          inquire(unit=funit, opened=is_used)
111          if (.not. is_used) exit
112       end do
113       open(funit,file='namelist.wps',status='old',form='formatted',err=1000)
114       read(funit,share)
115       read(funit,geogrid)
116       close(funit)
118 ! BUG: More properly handle debug_level in module_debug
119       if (debug_level.gt.100) then
120          call set_debug_level(DEBUG)
121       else
122          call set_debug_level(WARN)
123       end if
125       call mprintf(.true.,LOGFILE,'Using the following namelist variables:')
126       call mprintf(.true.,LOGFILE,'&SHARE')
127       call mprintf(.true.,LOGFILE,'  WRF_CORE         = %s',s1=wrf_core)
128       call mprintf(.true.,LOGFILE,'  MAX_DOM          = %i',i1=max_dom)
129       call mprintf(.true.,LOGFILE,'  START_YEAR       = %i',i1=start_year(1))
130       do i=2,max_dom
131          call mprintf(.true.,LOGFILE,'                   = %i',i1=start_year(i))
132       end do
133       call mprintf(.true.,LOGFILE,'  START_MONTH      = %i',i1=start_month(1))
134       do i=2,max_dom
135          call mprintf(.true.,LOGFILE,'                   = %i',i1=start_month(i))
136       end do
137       call mprintf(.true.,LOGFILE,'  START_DAY        = %i',i1=start_day(1))
138       do i=2,max_dom
139          call mprintf(.true.,LOGFILE,'                   = %i',i1=start_day(i))
140       end do
141       call mprintf(.true.,LOGFILE,'  START_HOUR       = %i',i1=start_hour(1))
142       do i=2,max_dom
143          call mprintf(.true.,LOGFILE,'                   = %i',i1=start_hour(i))
144       end do
145       call mprintf(.true.,LOGFILE,'  START_MINUTE     = %i',i1=start_minute(1))
146       do i=2,max_dom
147          call mprintf(.true.,LOGFILE,'                   = %i',i1=start_minute(i))
148       end do
149       call mprintf(.true.,LOGFILE,'  START_SECOND     = %i',i1=start_second(1))
150       do i=2,max_dom
151          call mprintf(.true.,LOGFILE,'                   = %i',i1=start_second(i))
152       end do
153       call mprintf(.true.,LOGFILE,'  END_YEAR         = %i',i1=end_year(1))
154       do i=2,max_dom
155          call mprintf(.true.,LOGFILE,'                   = %i',i1=end_year(i))
156       end do
157       call mprintf(.true.,LOGFILE,'  END_MONTH        = %i',i1=end_month(1))
158       do i=2,max_dom
159          call mprintf(.true.,LOGFILE,'                   = %i',i1=end_month(i))
160       end do
161       call mprintf(.true.,LOGFILE,'  END_DAY          = %i',i1=end_day(1))
162       do i=2,max_dom
163          call mprintf(.true.,LOGFILE,'                   = %i',i1=end_day(i))
164       end do
165       call mprintf(.true.,LOGFILE,'  END_HOUR         = %i',i1=end_hour(1))
166       do i=2,max_dom
167          call mprintf(.true.,LOGFILE,'                   = %i',i1=end_hour(i))
168       end do
169       call mprintf(.true.,LOGFILE,'  END_MINUTE       = %i',i1=end_minute(1))
170       do i=2,max_dom
171          call mprintf(.true.,LOGFILE,'                   = %i',i1=end_minute(i))
172       end do
173       call mprintf(.true.,LOGFILE,'  END_SECOND       = %i',i1=end_second(1))
174       do i=2,max_dom
175          call mprintf(.true.,LOGFILE,'                   = %i',i1=end_second(i))
176       end do
177       call mprintf(.true.,LOGFILE,'  START_DATE       = %s',s1=start_date(1))
178       do i=2,max_dom
179          call mprintf(.true.,LOGFILE,'                   = %s',s1=start_date(i))
180       end do
181       call mprintf(.true.,LOGFILE,'  END_DATE         = %s',s1=end_date(1))
182       do i=2,max_dom
183          call mprintf(.true.,LOGFILE,'                   = %s',s1=end_date(i))
184       end do
185       call mprintf(.true.,LOGFILE,'  INTERVAL_SECONDS = %i',i1=interval_seconds)
186       call mprintf(.true.,LOGFILE,'  IO_FORM_GEOGRID  = %i',i1=io_form_geogrid)
187       call mprintf(.true.,LOGFILE,'  OPT_OUTPUT_FROM_GEOGRID_PATH = %s',s1=opt_output_from_geogrid_path)
188       call mprintf(.true.,LOGFILE,'  DEBUG_LEVEL      = %i',i1=debug_level)
189       call mprintf(.true.,LOGFILE,'/')
191       call mprintf(.true.,LOGFILE,'&GEOGRID')
192       call mprintf(.true.,LOGFILE,'  PARENT_ID         = %i',i1=parent_id(1))
193       do i=2,max_dom
194          call mprintf(.true.,LOGFILE,'                    = %i',i1=parent_id(i))
195       end do
196       call mprintf(.true.,LOGFILE,'  PARENT_GRID_RATIO = %i',i1=parent_grid_ratio(1))
197       do i=2,max_dom
198          call mprintf(.true.,LOGFILE,'                    = %i',i1=parent_grid_ratio(i))
199       end do
200       call mprintf(.true.,LOGFILE,'  I_PARENT_START    = %i',i1=i_parent_start(1))
201       do i=2,max_dom
202          call mprintf(.true.,LOGFILE,'                    = %i',i1=i_parent_start(i))
203       end do
204       call mprintf(.true.,LOGFILE,'  J_PARENT_START    = %i',i1=j_parent_start(1))
205       do i=2,max_dom
206          call mprintf(.true.,LOGFILE,'                    = %i',i1=j_parent_start(i))
207       end do
208       call mprintf(.true.,LOGFILE,'  S_WE              = %i',i1=s_we(1))
209       do i=2,max_dom
210          call mprintf(.true.,LOGFILE,'                    = %i',i1=s_we(i))
211       end do
212       call mprintf(.true.,LOGFILE,'  E_WE              = %i',i1=e_we(1))
213       do i=2,max_dom
214          call mprintf(.true.,LOGFILE,'                    = %i',i1=e_we(i))
215       end do
216       call mprintf(.true.,LOGFILE,'  S_SN              = %i',i1=s_sn(1))
217       do i=2,max_dom
218          call mprintf(.true.,LOGFILE,'                    = %i',i1=s_sn(i))
219       end do
220       call mprintf(.true.,LOGFILE,'  E_SN              = %i',i1=e_sn(1))
221       do i=2,max_dom
222          call mprintf(.true.,LOGFILE,'                    = %i',i1=e_sn(i))
223       end do
224       call mprintf(.true.,LOGFILE,'  GEOG_DATA_RES     = %s',s1=geog_data_res(1))
225       do i=2,max_dom
226          call mprintf(.true.,LOGFILE,'                    = %s',s1=geog_data_res(i))
227       end do
228       call mprintf(.true.,LOGFILE,'  DX                = %f',f1=dx)
229       call mprintf(.true.,LOGFILE,'  DY                = %f',f1=dy)
230       call mprintf(.true.,LOGFILE,'  MAP_PROJ          = %s',s1=map_proj)
231       call mprintf(.true.,LOGFILE,'  REF_LAT           = %f',f1=ref_lat)
232       call mprintf(.true.,LOGFILE,'  REF_LON           = %f',f1=ref_lon)
233       call mprintf(.true.,LOGFILE,'  REF_X             = %f',f1=ref_x)
234       call mprintf(.true.,LOGFILE,'  REF_Y             = %f',f1=ref_y)
235       call mprintf(.true.,LOGFILE,'  TRUELAT1          = %f',f1=truelat1)
236       call mprintf(.true.,LOGFILE,'  TRUELAT2          = %f',f1=truelat2)
237       call mprintf(.true.,LOGFILE,'  STAND_LON         = %f',f1=stand_lon)
238       call mprintf(.true.,LOGFILE,'  GEOG_DATA_PATH    = %s',s1=geog_data_path)
239       call mprintf(.true.,LOGFILE,'  OPT_GEOGRID_TBL_PATH = %s',s1=opt_geogrid_tbl_path)
240       call mprintf(.true.,LOGFILE,'/')
242       dxkm = dx
243       dykm = dy
245       known_lat = ref_lat
246       known_lon = ref_lon
247       known_x = ref_x
248       known_y = ref_y
250       ! Convert wrf_core to uppercase letters
251       do i=1,3
252          if (ichar(wrf_core(i:i)) >= 97) wrf_core(i:i) = char(ichar(wrf_core(i:i))-32)
253       end do
255       ! Before doing anything else, we must have a valid grid type 
256       gridtype = ' '
257       if (wrf_core == 'ARW') then
258          gridtype = 'C'
259          dyn_opt = 2
260       else if (wrf_core == 'NMM') then
261          gridtype = 'E'
262          dyn_opt = 4
263       end if
265       ! Next, if this is NMM, we need to subtract 1 from the specified E_WE and E_SN;
266       !    for some reason, these two variables need to be set to 1 larger than they 
267       !    really ought to be in the WRF namelist, so, to be consistent, we will do 
268       !    the same in the WPS namelist
269       if (gridtype == 'E') then
270          do i=1,max_dom
271             e_we(i) = e_we(i) - 1 
272             e_sn(i) = e_sn(i) - 1 
273          end do 
274       end if
275   
276       call mprintf(gridtype /= 'C' .and. gridtype /= 'E', ERROR, &
277                    'A valid wrf_core must be specified in the namelist. '// &
278                    'Currently, only "ARW" and "NMM" are supported.')
280       call mprintf(max_dom > MAX_DOMAINS, ERROR, &
281                    'In namelist, max_dom must be <= %i. To run with more'// &
282                    ' than %i domains, increase the MAX_DOMAINS parameter.', &
283                    i1=MAX_DOMAINS, i2=MAX_DOMAINS)
285       ! Every domain must have a valid parent id
286       do i=2,max_dom
287          call mprintf(parent_id(i) <= 0 .or. parent_id(i) >= i, ERROR, &
288                       'In namelist, the parent_id of domain %i must be in '// &
289                       'the range 1 to %i.', i1=i, i2=i-1)
290       end do
291   
292       ! Check for valid geog_data_path
293       j=1
294       do i=1,len(geog_data_path)
295          geog_data_path(j:j) = geog_data_path(i:i)
296          if (geog_data_path(i:i) /= ' ') j = j + 1
297       end do
298       if (geog_data_path(1:1) == ' ') then
299          call mprintf(.true.,ERROR,'In namelist, geog_data_path must be specified.')
300       end if
301       j = len_trim(geog_data_path)
302       if (j >= 128) then
303          call mprintf(.true.,ERROR, &
304                       'In namelist, geog_data_path must be strictly less '// &
305                       'than 128 characters in length.')
306       else
307          if (geog_data_path(j:j) /= '/') then
308             geog_data_path(j+1:j+1) = '/'
309          end if
310       end if
312       ! Paths need to end with a /
313       j = len_trim(opt_geogrid_tbl_path)
314       if (opt_geogrid_tbl_path(j:j) /= '/') then
315          opt_geogrid_tbl_path(j+1:j+1) = '/'
316       end if
318       j = len_trim(opt_output_from_geogrid_path)
319       if (opt_output_from_geogrid_path(j:j) /= '/') then
320          opt_output_from_geogrid_path(j+1:j+1) = '/'
321       end if
322   
323       ! Handle IOFORM+100 to do tiled IO
324       if (io_form_geogrid > 100) then
325          do_tiled_output = .true.
326          io_form_geogrid = io_form_geogrid - 100
327       else
328          do_tiled_output = .false.
329       end if
330   
331       ! Check for valid io_form_geogrid
332       if ( &
333 #ifdef IO_BINARY
334           io_form_geogrid /= BINARY .and. &
335 #endif
336 #ifdef IO_NETCDF
337           io_form_geogrid /= NETCDF .and. &
338 #endif
339 #ifdef IO_GRIB1
340           io_form_geogrid /= GRIB1 .and. &
341 #endif
342           .true. ) then
343          call mprintf(.true.,WARN,'Valid io_form_geogrid values are:')
344 #ifdef IO_BINARY
345          call mprintf(.true.,WARN,'       %i (=BINARY)',i1=BINARY)
346 #endif
347 #ifdef IO_NETCDF
348          call mprintf(.true.,WARN,'       %i (=NETCDF)',i1=NETCDF)
349 #endif
350 #ifdef IO_GRIB1
351          call mprintf(.true.,WARN,'       %i (=GRIB1)',i1=GRIB1)
352 #endif
353          call mprintf(.true.,ERROR,'No valid value for io_form_geogrid was specified in the namelist.')
354       end if
355       io_form_output = io_form_geogrid
356   
357       ! Convert map_proj to uppercase letters
358       do i=1,len(map_proj)
359          if (ichar(map_proj(i:i)) >= 97) map_proj(i:i) = char(ichar(map_proj(i:i))-32)
360       end do
361   
362       ! Assign parameters to module variables
363       if ((index(map_proj, 'LAMBERT') /= 0) .and. &
364           (len_trim(map_proj) == len('LAMBERT'))) then
365          iproj_type = PROJ_LC 
366   
367       else if ((index(map_proj, 'MERCATOR') /= 0) .and. &
368                (len_trim(map_proj) == len('MERCATOR'))) then
369          iproj_type = PROJ_MERC 
370   
371       else if ((index(map_proj, 'POLAR') /= 0) .and. &
372                (len_trim(map_proj) == len('POLAR'))) then
373          iproj_type = PROJ_PS 
374   
375       else if ((index(map_proj, 'ROTATED_LL') /= 0) .and. &
376                (len_trim(map_proj) == len('ROTATED_LL'))) then
377          iproj_type = PROJ_ROTLL 
378   
379       else
380          call mprintf(.true.,ERROR,&
381                       'In namelist, invalid map_proj specified. Valid '// &
382                       'projections are "lambert", "mercator", "polar", '// &
383                       'and "rotated_ll".')
384       end if
385   
386       n_domains = max_dom
387   
388       ! For C grid, let ixdim and jydim be the number of mass points in 
389       !    each direction; for E grid, we will put the row and column back
390       !    later; maybe this should be changed to be more clear, though.
391       do i=1,n_domains
392          ixdim(i) = e_we(i) - s_we(i) + 1
393          jydim(i) = e_sn(i) - s_sn(i) + 1
394       end do
395   
396       if (gridtype == 'E') then
397          phi = dykm*real(jydim(1)-1)/2.
398          lambda = dxkm*real(ixdim(1)-1)
399       end if
401       ! If the user hasn't supplied a known_x and known_y, assume the center of domain 1
402       if (gridtype == 'E' .and. (known_x /= NAN .or. known_y /= NAN)) then
403          call mprintf(.true.,WARN, &
404                       'Namelist variables ref_x and ref_y cannot be used for NMM grids.'// &
405                       ' (ref_lat, ref_lon) will refer to the center of the coarse grid.')
406       else if (gridtype == 'C') then
407          if (known_x == NAN .and. known_y == NAN) then
408             known_x = ixdim(1) / 2.
409             known_y = jydim(1) / 2.
410          else if (known_x == NAN .or. known_y == NAN) then
411             call mprintf(.true.,ERROR, &
412                       'In namelist.wps, neither or both of ref_x, ref_y must be specified.')
413          end if 
414       end if
416       ! Checks specific to E grid
417       if (gridtype == 'E') then
418   
419          ! E grid supports only the rotated lat/lon projection
420          if (iproj_type /= PROJ_ROTLL) then
421             call mprintf(.true., WARN, &
422                          'For the NMM core, projection type must be rotated '// &
423                          'lat/lon (map_proj=rotated_ll)')
424             call mprintf(.true.,WARN,'Projection will be set to rotated_ll')
425             iproj_type = PROJ_ROTLL
426          end if
427    
428          ! In the following check, add back the 1 that we had to subtract above 
429          !   for the sake of being consistent with WRF namelist
430          call mprintf(mod(e_sn(1)+1,2) /= 0, ERROR, &
431                       'For the NMM core, E_SN must be an even number for grid %i.', i1=1)
433          do i=1,n_domains
434             call mprintf((parent_grid_ratio(i) /= 3 .and. i > 1), ERROR, &
435                          'For the NMM core, the parent_grid_ratio must be 3.') 
436          end do
438          ! Check that nests have an acceptable number of grid points in each dimension
439 !         do i=2,n_domains
440 !            rparent_gridpts = real(ixdim(i)+2)/real(parent_grid_ratio(i))
441 !            if (floor(rparent_gridpts) /= ceiling(rparent_gridpts)) then
442 !               call mprintf(.true.,ERROR,'For nest %i, e_we must be 3n-2 '// &
443 !                            'for some integer n > 1.', &
444 !                            i1=i)
445 !            end if
446 !            rparent_gridpts = real(jydim(i)+2)/real(parent_grid_ratio(i))
447 !            if (floor(rparent_gridpts) /= ceiling(rparent_gridpts)) then
448 !               call mprintf(.true.,ERROR,'For nest %i, e_sn must be 3n-2 '// &
449 !                            'for some odd integer n > 1.', &
450 !                            i1=i)
451 !            end if
452 !         end do
453    
454       ! Checks specific to C grid
455       else if (gridtype == 'C') then
456   
457          ! C grid does not support the rotated lat/lon projection
458          call mprintf((iproj_type == PROJ_ROTLL), ERROR, &
459                       'Rotated lat/lon projection is not supported for the ARW core. '// &
460                       'Valid projecitons are "lambert", "mercator", and "polar".')
462          ! Check that nests have an acceptable number of grid points in each dimension
463          do i=2,n_domains
464             rparent_gridpts = real(ixdim(i)-1)/real(parent_grid_ratio(i))
465             if (floor(rparent_gridpts) /= ceiling(rparent_gridpts)) then
466                call mprintf(.true.,ERROR,'For nest %i, (e_we-s_we+1) must be one greater '// &
467                             'than an interger multiple of the parent_grid_ratio of %i.', &
468                             i1=i, i2=parent_grid_ratio(i))
469             end if
470             rparent_gridpts = real(jydim(i)-1)/real(parent_grid_ratio(i))
471             if (floor(rparent_gridpts) /= ceiling(rparent_gridpts)) then
472                call mprintf(.true.,ERROR,'For nest %i, (e_sn-s_sn+1) must be one greater '// &
473                             'than an interger multiple of the parent_grid_ratio of %i.', &
474                             i1=i, i2=parent_grid_ratio(i))
475             end if
476          end do
477       end if
478   
479       do i=1,n_domains
480          parent_ll_x(i) = real(i_parent_start(i))
481          parent_ll_y(i) = real(j_parent_start(i))
482          parent_ur_x(i) = real(i_parent_start(i))+real(ixdim(i))/real(parent_grid_ratio(i))-1.
483          parent_ur_y(i) = real(j_parent_start(i))+real(jydim(i))/real(parent_grid_ratio(i))-1.
484       end do
485   
486       return
487   
488  1000 call mprintf(.true.,ERROR,'Error opening file namelist.wps')
490    end subroutine get_grid_params
491   
492 end module gridinfo_module