1 !*****************************************************************************!
4 ! Questions, comments, suggestions, even complaints should be directed to: !
10 ! Subroutine READ_NAMELIST !
11 ! Subroutine PARSE_TABLE !
12 ! Subroutine CLEAR_STORAGE !
13 ! Subroutine RD_GRIB !
14 ! Subroutine RD_GRIB2 !
15 ! Subroutine PUT_STORAGE !
17 ! Subroutine C_CLOSE !
20 ! Subroutine FILE_DELETE !
22 ! Kevin W. Manning, NCAR/MMM - original 'pregrid' code, 1998-2001 !
23 ! Jim Bresch, Michael Duda, Dave Gill, NCAR/MMM - adapted for WPS, 2006 !
25 !*****************************************************************************!
27 !*****************************************************************************!
29 ! This program reads GRIB-formatted data and puts it into intermediate format !
30 ! for passing data to a horizontal interpolation program. The intermediate !
31 ! format can be for WPS, SI, or MM5. !
33 ! The program tries to read from files called "GRIBFILE.AAA", "GRIBFILE.AAB", !
34 ! "GRIBFILE.AAC", ... "GRIBFILE.ABA", "GRIBFILE.ABB", ... "GRIBFILE.ZZZ" until!
35 ! it cannot find a file. This naming format allows for up to 17576 files, !
36 ! which should be enough for most applications. !
38 ! The program searches through those "GRIBFILE.???" files, and pulls out all !
39 ! the requested fields which fall between a starting date and an ending date. !
40 ! It writes the fields from a given time period to a file named according to !
41 ! the date and hour, i.e., "FILE:YYYY-MM-DD_HH" !
43 !*****************************************************************************!
52 use misc_definitions_module
57 integer :: nunit1 = 12
58 character(LEN=132) :: gribflnm = 'GRIBFILE.AAA ' ! won't work with len=12
60 integer :: debug_level
62 integer , parameter :: maxlvl = 150
64 real , dimension(maxlvl) :: plvl
69 real :: startlat, startlon, deltalat, deltalon
71 character (LEN=9) :: field
72 character (LEN=3) :: out_format
73 character (LEN=MAX_FILENAME_LEN) :: prefix
77 integer, dimension(255) :: iuarr = 0
79 character (LEN=19) :: HSTART, HEND, HDATE
80 character(LEN=19) :: hsave = '0000-00-00_00:00:00'
85 logical :: ordered_by_date
86 integer :: grib_version
87 integer :: vtable_columns
90 call mprintf(.true.,STDOUT,' *** Starting program ungrib.exe *** ')
91 call mprintf(.true.,LOGFILE,' *** Starting program ungrib.exe *** ')
93 ! Read the namelist, and return the information we want:
95 call read_namelist(hstart, hend, interval, ntimes, &
96 ordered_by_date, debug_level, out_format, prefix)
98 call mprintf(.true.,INFORM,"Interval value: %i seconds or %f hours", &
99 i1=interval, f1=float(interval)/3600.)
101 call mprintf(.true.,STDOUT,'Path to intermediate files is %s',s1=get_path(prefix))
102 call mprintf(.true.,LOGFILE,'Path to intermediate files is %s',s1=get_path(prefix))
105 ! Determine GRIB Edition number
107 call edition_num(nunit1, gribflnm, grib_version, ierr)
108 call mprintf((ierr.eq.3),ERROR,"GRIB file problem")
109 if (grib_version.eq.2) then
111 #if defined (USE_PNG) && (USE_JPEG2000)
112 call mprintf(.true.,INFORM, &
113 "Linked in png and jpeg libraries for Grib Edition 2")
115 call mprintf(.true.,STDOUT,"WARNING - Grib Edition 2 data detected, and")
116 call mprintf(.true.,STDOUT," - png and jpeg libs were NOT selected")
117 call mprintf(.true.,STDOUT," - during the build.")
118 call mprintf(.true.,STDOUT,"Stopping")
119 call mprintf(.true.,LOGFILE,"WARNING - Grib Edition 2 data detected, and")
120 call mprintf(.true.,LOGFILE," - png and jpeg libs were NOT selected")
121 call mprintf(.true.,LOGFILE," - during the build.")
122 call mprintf(.true.,LOGFILE,"Stopping")
123 call mprintf(.true.,ERROR,"NEED_GRIB2_LIBS")
128 call mprintf(.true.,INFORM,"Reading Grib Edition %i", i1=grib_version)
131 ! Read the "Vtable" file, and put the information contained therein into
132 ! the module "table".
134 call parse_table(debug_level,vtable_columns)
136 call mprintf(.true.,DEBUG,"Parsed the vtable.")
139 ! Initialize the input filename to GRIBFILE.AA{character just before A}
140 ! That way, when we update the filename below for the first time, it will
141 ! have the correct value of GRIBFILE.AAA.
143 gribflnm(12:12)=char(ichar(gribflnm(12:12))-1)
146 ! LOOP2 cycles through the list of files named GRIBFILE.???, until it finds
147 ! a non-existent file. Then we exit
151 ! At the beginning of LOOP2 update the input filename.
152 if (gribflnm(12:12).eq.'Z') then
153 if (gribflnm(11:11).eq.'Z') then
154 gribflnm(10:10) = char(ichar(gribflnm(10:10))+1)
155 gribflnm(11:11) = 'A'
157 gribflnm(11:11) = char(ichar(gribflnm(11:11))+1)
159 gribflnm(12:12) = 'A'
161 gribflnm(12:12) = char(ichar(gribflnm(12:12))+1)
164 ! Set READIT to .TRUE., meaning that we have not read any records yet
165 ! from the file GRIBFLNM.
167 call mprintf(.true.,DEBUG,"Reading from gribflnm %s ",s1=gribflnm)
169 readit = .TRUE. ! i.e., "Yes, we want to read a record."
172 ! LOOP1 reads through the file GRIBFLNM, exiting under two conditions:
173 ! 1) We have hit the end-of-file
174 ! 2) We have read past the ending date HEND.
176 ! Condition 2 assumes that the data in file GRIBFLNM are ordered in time.
179 ! At the beginning of LOOP1, we are at a new time period.
180 ! Clear the storage arrays and associated level information.
185 ! LOOP0 reads through the file GRIBFLNM, looking for data of the current
186 ! date. It exits under the following conditions.
187 ! 1) We have hit the end-of-file
188 ! 2) The GRIBFLNM variable has been updated to a nonexistent file.
189 ! 3) We start reading a new date and the data are assumed to be
191 ! 4) We have a valid record and the data are not assumed to be
196 ! If we need to read a new grib record, then read one.
199 if (grib_version.ne.2) then
200 call mprintf(.true.,DEBUG, &
201 "Calling rd_grib1 with iunit %i", i1=nunit1)
202 call mprintf(.true.,DEBUG, &
203 "flnm = %s",s1=gribflnm)
204 ! Read one record at a time from GRIB1 (and older Editions)
205 call rd_grib1(nunit1, gribflnm, level, field, &
206 hdate, ierr, iuarr, debug_level)
209 ! Read one file of records from GRIB2.
210 call mprintf(.true.,DEBUG,"Calling rd_grib2")
211 call rd_grib2(nunit1, gribflnm, hdate, &
212 grib_version, ierr, debug_level)
217 call mprintf(.true.,DEBUG,"ierr = %i ",i1=ierr)
219 ! We have hit the end of a file. Exit LOOP0 so we can
220 ! write output for date HDATE, and then exit LOOP1
221 ! to update the GRIBFLNM
227 ! We have hit the end of all the files. We can exit LOOP2
228 ! because there are no more files to read.
232 call mprintf(.true.,DEBUG, &
233 "Read a record %s with date %s", s1=field,s2=hdate(1:13))
237 call mprintf(.true.,DEBUG, &
238 "hdate = %s , hsave = %s ",s1=hdate(1:13), s2=hsave(1:13) )
240 ! if (hdate < hstart) then
241 ! ! The data read has a date HDATE earlier than the starting
242 ! ! date HSTART. So cycle LOOP0 to read the the next GRIB record.
247 if (FIELD.EQ.'NULL') then
248 ! The data read does not match any fields requested
249 ! in the Vtable. So cycle LOOP0 to read the next GRIB record.
254 if (ordered_by_date .and. (hdate > hsave)) then
256 ! Exit LOOP0, because we started to read data from another
259 call mprintf(.true.,DEBUG, &
260 "hdate %s > hsave %s so exit LOOP0",s1=hdate,s2=hsave)
262 ! We set READIT to FALSE because we have not yet processed
263 ! the data from this record, and we will want to process this
264 ! data on the next pass of LOOP1 (referring to the next time
265 ! period of interest.
273 ! When we have reached this point, we have a data array ARRAY which has
274 ! some data we want to save, with field name FIELD at pressure level
275 ! LEVEL (Pa). Dimensions of this data are map%nx and map%ny. Put
276 ! this data into storage.
278 if (((field == "SST").or.(field == "SKINTEMP")) .and. &
279 (level /= 200100.)) level = 200100.
281 call mprintf((.not.allocated(rdatarray)),ERROR, &
282 "GRIB data slab not allocated in ungrib.F before call to put_storage.")
283 call put_storage(iplvl,field, &
284 reshape(rdatarray(1:map%nx*map%ny),(/map%nx, map%ny/)),&
286 deallocate(rdatarray)
288 ! Since we processed the record we just read, we set
289 ! READIT to .TRUE. so that LOOP0 will read the next record.
292 if (.not. ordered_by_date) then
293 if (hdate >= hstart) then
301 ! When we have reached this point, we have either hit the end of file, or
302 ! hit the end of the current date. Either way, we want to output
303 ! the data found for this date. This current date is in HSAVE.
304 ! However, if (HSAVE == 0000-00-00_00:00:00), no output is necessary,
305 ! because that 0000 date is the flag for the very opening of a file.
307 if ((hsave(1:4).ne.'0000').and.(hsave.le.hend)) then
308 if (debug_level .gt. 100) then
309 print*, 'Calling output: '//hsave(1:13)
310 call mprintf(.true.,DEBUG,"Calling output: %s ",s1=hsave(1:13))
312 call output(hsave, nlvl, maxlvl, plvl, interval, 1, out_format, prefix, debug_level)
315 ! If the next record we process has a date later than HEND,
316 ! then time to exit LOOP1.
317 if ((ordered_by_date) .and. (hdate.gt.hend)) exit LOOP1
323 ! If we hit the end-of-file, its time to exit LOOP1 so we can
324 ! increment the GRIBFLNM to read the next file.
325 if (ierr.eq.1) exit LOOP1
329 ! When we have reached this point, we read all the data we want to from
330 ! file GRIBFLNM (either because we reached the end-of-file, or we
331 ! read past the date HEND). So we close the file and cycle LOOP2 to read
334 if (grib_version.ne.2) then
335 call c_close(iuarr(nunit1), debug_level, ierr)
338 hsave = '0000-00-00_00:00:00'
342 ! Now Reread, process, and reoutput.
344 call mprintf(.true.,INFORM,"First pass done, doing a reprocess")
346 call rrpr(hstart, ntimes, interval, nlvl, maxlvl, plvl, debug_level, out_format, prefix)
348 ! Make sure the filedates are in order, with an inefficient sort:
352 ! Interpolate temporally to fill in missing times:
354 call datint(filedates, nfiles, hstart, ntimes, interval, out_format, prefix)
356 ! Now delete the temporary files:
358 call file_delete(filedates, nfiles, trim(get_path(prefix))//'PFILE:', interval)
360 ! And Now we are done:
362 call mprintf(.true.,STDOUT,'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!')
363 call mprintf(.true.,STDOUT,'! Successful completion of ungrib. !')
364 ! call mprintf(.true.,STDOUT,"! We're hauling gear at Bandimere. !")
365 call mprintf(.true.,STDOUT,'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!')
367 call mprintf(.true.,LOGFILE,' *** Successful completion of program ungrib.exe *** ')
372 subroutine sort_filedates
379 do while ( .not. done)
382 if (filedates(n) > filedates(n+1)) then
383 filedates(size(filedates)) = filedates(n)
384 filedates(n) = filedates(n+1)
385 filedates(n+1) = filedates(size(filedates))
386 filedates(size(filedates)) = '0000-00-00 00:00:00.0000'
392 end subroutine sort_filedates