Modify check for global grid for Gaussian and lat/lon grids in rd_grib1.F.
[WPS-merge.git] / ungrib / src / read_namelist.F
blob4d8133d61ef50d638131e5f6c6fbcea46fcc0f20
1 subroutine read_namelist(hstart, hend, delta_time, ntimes,&
2      ordered_by_date, debug_level, out_format, prefix,    &
3      add_lvls, new_plvl_in, interp_type, ec_rec_len)
5   use misc_definitions_module
6   use module_debug
8   implicit none
9   integer , parameter :: maxim_doms = 21
10   character(len=200) :: extdataroot, file_name_namelist
11   character(len=19) :: hstart, hend
12   integer :: delta_time
13   integer :: ntimes
14   logical :: ordered_by_date
15   integer :: debug_level
16   real, dimension(:) :: new_plvl_in
17   logical :: add_lvls
18   integer :: interp_type, ec_rec_len
20   integer :: ierr
21   integer :: idts
23 ! Declare the namelist variables:
25   integer , dimension(maxim_doms) :: start_year
26   integer , dimension(maxim_doms) :: start_month
27   integer , dimension(maxim_doms) :: start_day
28   integer , dimension(maxim_doms) :: start_hour
29   integer , dimension(maxim_doms) :: start_minute
30   integer , dimension(maxim_doms) :: start_second
32   integer , dimension(maxim_doms) :: end_year
33   integer , dimension(maxim_doms) :: end_month
34   integer , dimension(maxim_doms) :: end_day
35   integer , dimension(maxim_doms) :: end_hour
36   integer , dimension(maxim_doms) :: end_minute
37   integer , dimension(maxim_doms) :: end_second
39   logical , dimension(maxim_doms) :: active_grid
40   integer , dimension(maxim_doms) :: subgrid_ratio_x
41   integer , dimension(maxim_doms) :: subgrid_ratio_y
43   character (len=128) , dimension(maxim_doms) :: start_date, end_date
44   character (len=MAX_FILENAME_LEN) :: opt_output_from_geogrid_path
45   integer :: interval_seconds = 0
46   character (len=3) :: wrf_core = 'ARW'
47   integer :: max_dom, io_form_geogrid
49   character(len=3) :: out_format
50   character(len=MAX_FILENAME_LEN) :: prefix
51   logical :: nocolons
53   real :: target_end, incr
54   integer :: il
56   real, dimension(:), allocatable :: new_plvl
58   namelist /share/ wrf_core, max_dom, &
59        start_year, start_month, start_day, start_hour, &
60        start_minute, start_second, &
61        end_year, end_month, end_day, end_hour, &
62        end_minute, end_second,&
63        interval_seconds, &
64        start_date, end_date, &
65        io_form_geogrid, opt_output_from_geogrid_path, &
66        debug_level, active_grid, &
67        subgrid_ratio_x, subgrid_ratio_y, &
68        nocolons
70   namelist /ungrib/ out_format, &
71        ordered_by_date, prefix, &
72        add_lvls, new_plvl, interp_type, ec_rec_len
74   allocate(new_plvl(size(new_plvl_in)))
76   start_year = 0
77   start_month = 0
78   start_day = 0
79   start_hour = 0
80   start_minute = 0
81   start_second = 0
83   end_year = 0
84   end_month = 0
85   end_day = 0
86   end_hour = 0
87   end_minute = 0
88   end_second = 0
90   ! Set defaults. 
91   io_form_geogrid = 2
92   max_dom = 1
93   wrf_core = 'ARW'
94   debug_level = 0
95   nocolons = .false.
97   add_lvls = .false.
98   new_plvl = -99999.
99   interp_type = 0
100   ec_rec_len = 0
102 ! Start routine:
104 ! Build the namelist file name:
106 #ifndef __crayx1
107   CALL GETENV('EXT_DATAROOT',extdataroot)
108 #endif
109   file_name_namelist =  'namelist.wps'
111 ! Open the namelist file:
112   open(10, file=file_name_namelist, status='old', iostat=ierr)
113   call mprintf((ierr.ne.0),ERROR,"**** Error opening namelist file namelist.wps")
115    REWIND (10) 
117   ! set default:
118   ordered_by_date = .TRUE.
119   start_date(1)(1:4) = '0000'
120   end_date(1)(1:4)   = '0000'
122   read(10,NML=share)
124   if (debug_level.gt.100) then
125      call set_debug_level(DEBUG)
126   else
127      call set_debug_level(WARN)
128   end if
131 ! Build the Starting date HSTART and the ending date HEND from the namelist
132 ! date/time information. start_date takes priority over the multi-variable method.
134   if ( start_date(1)(1:4) .eq. '0000' ) then
135     call build_hdate(hstart, start_year(1), start_month(1), start_day(1), start_hour(1), &
136        start_minute(1), start_second(1))
137   else
138     hstart = start_date(1)(1:19)
139   endif
140   if ( end_date(1)(1:4) .eq. '0000' ) then
141     call build_hdate(hend, end_year(1), end_month(1), end_day(1), end_hour(1), &
142        end_minute(1), end_second(1))
143   else
144     hend = end_date(1)(1:19)
145   endif
147 ! Compute the time difference between start date and end date:
149   call geth_idts(hend, hstart, idts)
151 ! Check that INTERVAL is greater than zero:
153   if (interval_seconds <= 0) then
154      call mprintf(.true.,STDOUT,"ERROR STOP IN READ_NAMELIST")
155      call mprintf(.true.,STDOUT,"INTERVAL must be greater than zero:")
156      call mprintf(.true.,STDOUT,"Start time: %s",s1=hstart)
157      call mprintf(.true.,STDOUT,"End time:   %s",s1=hend)
158      call mprintf(.true.,STDOUT,"INTERVAL:   %i",i1=interval_seconds)
159      call mprintf(.true.,LOGFILE,"ERROR STOP IN READ_NAMELIST")
160      call mprintf(.true.,LOGFILE,"INTERVAL must be greater than zero:")
161      call mprintf(.true.,LOGFILE,"Start time: %s",s1=hstart)
162      call mprintf(.true.,LOGFILE,"End time:   %s",s1=hend)
163      call mprintf(.true.,LOGFILE,"INTERVAL:   %i",i1=interval_seconds)
164      call mprintf(.true.,ERROR,"Change your namelist, and resubmit")
165   endif
167 ! Check that the selected INTERVAL evenly fills difference between 
168 ! start time and end time:
170   if ((idts/interval_seconds)*interval_seconds /= idts) then
171      call mprintf(.true.,STDOUT,"ERROR STOP IN READ_NAMELIST")
172      call mprintf(.true.,STDOUT,"INTERVAL must fit evenly between start time and end time:")
173      call mprintf(.true.,STDOUT,"Start time: %s",s1=hstart)
174      call mprintf(.true.,STDOUT,"End time:   %s",s1=hend)
175      call mprintf(.true.,STDOUT,"INTERVAL  : %i seconds,  %f hours",&
176           i1=interval_seconds,f1=float(interval_seconds)/3600.)
177      call mprintf(.true.,LOGFILE,"ERROR STOP IN READ_NAMELIST")
178      call mprintf(.true.,LOGFILE,"INTERVAL must fit evenly between start time and end time:")
179      call mprintf(.true.,LOGFILE,"Start time: %s",s1=hstart)
180      call mprintf(.true.,LOGFILE,"End time:   %s",s1=hend)
181      call mprintf(.true.,LOGFILE,"INTERVAL  : %i seconds,  %f hours",&
182           i1=interval_seconds,f1=float(interval_seconds)/3600.)
183      call mprintf(.true.,ERROR,"Change your namelist, and resubmit")
184   endif
186 ! Check that start time is not later than end time:
188   if (hstart > hend) then
189      call mprintf(.true.,STDOUT,"ERROR STOP IN READ_NAMELIST")
190      call mprintf(.true.,STDOUT,"Start time must not be later than end time:")
191      call mprintf(.true.,STDOUT,"Start time: %s",s1=hstart)
192      call mprintf(.true.,STDOUT,"End time:   %s",s1=hend)
193      call mprintf(.true.,STDOUT,"INTERVAL:   %i",i1=interval_seconds)
194      call mprintf(.true.,LOGFILE,"ERROR STOP IN READ_NAMELIST")
195      call mprintf(.true.,LOGFILE,"Start time must not be later than end time:")
196      call mprintf(.true.,LOGFILE,"Start time: %s",s1=hstart)
197      call mprintf(.true.,LOGFILE,"End time:   %s",s1=hend)
198      call mprintf(.true.,LOGFILE,"INTERVAL:   %i",i1=interval_seconds)
199      call mprintf(.true.,ERROR,"Change your namelist, and resubmit")
200   endif
202 ! Compute the number of time periods to process:
204   ntimes = idts/interval_seconds + 1
206   call mprintf(.true.,STDOUT, &
207   "Start_date =  %s ,      End_date = %s ",s1=hstart,s2=hend)
208   call mprintf(.true.,LOGFILE, &
209   "Start_date =  %s ,      End_date = %s ",s1=hstart,s2=hend)
211   if (debug_level.gt.0) then
212      call mprintf(.true.,LOGFILE,"Namelist information (coarse domain): ")
213      call mprintf(.true.,LOGFILE,'  START_YEAR       = %i',i1=start_year(1))
214      call mprintf(.true.,LOGFILE,'  START_MONTH      = %i',i1=start_month(1))
215      call mprintf(.true.,LOGFILE,'  START_DAY        = %i',i1=start_day(1))
216      call mprintf(.true.,LOGFILE,'  START_HOUR       = %i',i1=start_hour(1))
217 !    call mprintf(.true.,LOGFILE,"start_minute = %i",i1=start_minute(1))
218 !    call mprintf(.true.,LOGFILE,"start_second = %i",i1=start_second(1))
219      call mprintf(.true.,LOGFILE,'  END_YEAR         = %i',i1=end_year(1))
220      call mprintf(.true.,LOGFILE,'  END_MONTH        = %i',i1=end_month(1))
221      call mprintf(.true.,LOGFILE,'  END_DAY          = %i',i1=end_day(1))
222      call mprintf(.true.,LOGFILE,'  END_HOUR         = %i',i1=end_hour(1))
223 !    call mprintf(.true.,LOGFILE,"end_minute = %i",i1=end_minute(1))
224 !    call mprintf(.true.,LOGFILE,"end_second = %i",i1=end_second(1))
225      call mprintf(.true.,LOGFILE,'  START_DATE       = %s',s1=start_date(1))
226      call mprintf(.true.,LOGFILE,'  END_DATE         = %s',s1=end_date(1))
227      call mprintf(.true.,LOGFILE,'  INTERVAL_SECONDS = %i',i1=interval_seconds)
228      call mprintf(.true.,LOGFILE,'  DEBUG_LEVEL      = %i',i1=debug_level)
229      call mprintf(.true.,LOGFILE,'/')
230   else
231      debug_level=0
232   endif
234   delta_time = interval_seconds
236   rewind(10)
237   out_format = 'WPS'
238   prefix = 'FILE'
239   read(10,NML=ungrib,END=100)
241      call mprintf(.true.,LOGFILE,'&UNGRIB')
242      call mprintf(.true.,LOGFILE,"out_format = %s",s1=out_format)
243      if (ordered_by_date) then
244        call mprintf(.true.,LOGFILE,"ordered_by_date = %s",s1='TRUE')
245      else
246        call mprintf(.true.,LOGFILE,"ordered_by_date = %s",s1='FALSE')
247      endif
248      call mprintf(.true.,LOGFILE,"prefix = %s",s1=trim(prefix))
249      call mprintf(.true.,LOGFILE,'/')
251 100  continue
252    if (out_format(1:2) .eq. 'WP' .or. out_format(1:2) .eq. 'wp') then
253      out_format = 'WPS'
254      call mprintf(.true.,STDOUT,'output format is WPS')
255      call mprintf(.true.,LOGFILE,'output format is WPS')
256    else if (out_format(1:2) .eq. 'SI' .or. out_format(1:2) .eq. 'si') then
257      out_format = 'SI '
258      call mprintf(.true.,STDOUT,'output format is SI')
259      call mprintf(.true.,LOGFILE,'output format is SI')
260    else if (out_format(1:2) .eq. 'MM' .or. out_format(1:2) .eq. 'mm') then
261      out_format = 'MM5'
262      call mprintf(.true.,STDOUT,'output format is MM5 pregrid')
263      call mprintf(.true.,LOGFILE,'output format is MM5 pregrid')
264    else 
265      call mprintf(.true.,ERROR, &
266  'read_namelist: I do not recognize the output format, %s , stopping.',s1=out_format)
267    endif
269 ! Check to see if I should create my own set of new_plvl's
270   if ( add_lvls .AND. new_plvl(2) > -99999. .AND. new_plvl(2) < 0.0 ) then
271     target_end = abs(new_plvl(2))
272     incr = new_plvl(3)
273     il = 2
274     make_plvl : do
275       if(il.gt.size(new_plvl)) then
276        call mprintf(.true.,ERROR,&
277         'Too many new levels specified via new_plvl. Increase maxlvl in ungrib.F')
278       end if
279       new_plvl(il) = new_plvl(il-1) - incr
280       ! If we are past the end of the range of pressures over which new levels
281       ! are to be created, then discard the pressure we just calculated. 
282       ! This occurs when the user-chosen increment did not evenly divide
283       ! the range of pressures over which new pressures were to be added.  
284       if ( new_plvl(il) < target_end ) then 
285         new_plvl(il) = -99999.
286         exit make_plvl
287       end if 
288       if ( new_plvl(il) == target_end ) exit make_plvl
289       il = il + 1
290     end do make_plvl
291   endif
293 ! Close the namelist file:
295   close(10)
297   new_plvl_in(:) = new_plvl(:)
298   deallocate(new_plvl)
299   
300 end subroutine read_namelist