NCEPLIBS-bufr  12.0.0
debufr.F90
Go to the documentation of this file.
1 
5 
12 
14  character(len=:), allocatable :: tbldir_f
15 
17  integer ltbd
18 
20  integer ludx
21 end module share_table_info
22 
56 subroutine fdebufr_c ( ofile, lenof, tbldir, lentd, tblfil, lentf, prmstg, lenps, basic, forcemt, cfms ) &
57  bind( c, name = 'fdebufr_f' )
58 
59  use iso_c_binding
60  use bufr_interface
62 
63  implicit none
64 
65  integer, parameter :: mxbf = 2500000
66  integer, parameter :: mxbfd4 = mxbf/4
67  integer, parameter :: mxds3 = 500
68  integer, parameter :: mxprms = 20
69 
70  character(kind=c_char,len=1), intent(in) :: ofile(*), tbldir(*), tblfil(*), prmstg(*)
71 
72  character(len=:), allocatable :: ofile_f, tblfil_f, prmstg_f
73 
74  integer(c_int), value, intent(in) :: lenof, lentd, lentf, lenps
75 
76  character(c_char), value, intent(in) :: basic, forcemt, cfms
77 
78  integer*4 :: isetprm, idxmsg, iupbs01, iupbs3, ireadsb
79  integer*4 :: nbyt, ierr
80 
81  logical exists
82 
83  character*120 cmorgc, cmgses, cmmtyp, cmmsbt, cmmsbti
84  character*20 ptag ( mxprms ), pvtag(2), cprmnm
85  character*8 cmgtag
86  character*6 cds3 ( mxds3 )
87  character opened, usemt, bfmg ( mxbf ), basic_f, forcemt_f, cfms_f
88 
89  integer ibfmg ( mxbfd4 ), lunit, nmsg, nsub, nsubt, ii, jj, nds3, nptag, npvtag, ipval, lcprmnm, ier, imgdt, ierme, &
90  iogce, lcmorgc, ierorgc, igses, lcmgses, iergses, iryr, irmo, irdy, irhr, irmi, irtret, &
91  mtyp, lcmmtyp, iermtyp, msbt, lcmmsbt, iermsbt, msbti, lcmmsbti, iermsbti, iersn
92 
93  equivalence( bfmg(1), ibfmg(1) )
94 
95 ! Initialize the values in the Share_Table_Info module.
96 
97  ludx = 93
98  ltbd = lentd
99  allocate( character(len=lentd) :: tbldir_f )
100  tbldir_f = transfer( tbldir(1:lentd), tbldir_f )
101 
102 ! Copy the other input C strings into Fortran strings.
103 
104  allocate( character(len=lenof) :: ofile_f )
105  ofile_f = transfer( ofile(1:lenof), ofile_f )
106  allocate( character(len=lentf) :: tblfil_f )
107  tblfil_f = transfer( tblfil(1:lentf), tblfil_f )
108  allocate( character(len=lenps) :: prmstg_f )
109  prmstg_f = transfer( prmstg(1:lenps), prmstg_f )
110  basic_f = basic
111  forcemt_f = forcemt
112  cfms_f = cfms
113 
114 ! Open the output file.
115 
116  open ( unit = 51, file = ofile_f )
117 
118 ! Note that in the below open statement we just need to specify a dummy placeholder file.
119 
120  lunit = 92
121  open ( unit = lunit, file = '/dev/null' )
122 
123  call datelen ( 10 )
124 
125 ! Initialize some other values.
126 
127  nmsg = 0
128  nsubt = 0
129 
130  opened = 'N'
131  usemt = 'N'
132 
133  do while ( .true. )
134 
135 ! Get the next message from the input BUFR file.
136 
137  call crbmg_c ( bfmg, mxbf, nbyt, ierr )
138 
139  if ( ierr .ne. 0 ) then
140 
141  if ( ierr .eq. -1 ) then
142  write ( 51, fmt = '( /, A, I7, A, I9, A )') 'Reached end of BUFR file; it contained a total of', nmsg, &
143  ' messages and', nsubt, ' subsets'
144  else
145  write ( 51, fmt = '( /, A, I4 )' ) 'Error while reading BUFR file; the return code from CRBMG = ', ierr
146  end if
147 
148  if ( ( basic_f .eq. 'N' ) .and. ( opened .eq. 'Y' ) ) then
149  write (51, fmt = '( /, A, / )' ) 'Here is the DX table that was generated:'
150  call dxdump ( lunit, 51 )
151  end if
152 
153 ! Close the output file, deallocate memory, and return.
154 
155  close ( 51 )
156  deallocate ( ofile_f )
157  deallocate ( tbldir_f )
158  deallocate ( tblfil_f )
159  deallocate ( prmstg_f )
160  return
161  end if
162 
163  if ( opened .eq. 'N' ) then
164 
165  if ( ( isetprm( 'MAXCD', mxds3 ) .ne. 0 ) .or. ( isetprm( 'MXMSGL', mxbf ) .ne. 0 ) .or. &
166  ( isetprm( 'MAXSS', 300000 ) .ne. 0 ) .or. ( isetprm( 'NFILES', 2 ) .ne. 0 ) ) then
167  print *, 'Error: Bad return from isetprm'
168  return
169  end if
170 
171 ! Process any dynamic allocation parameters that were passed in on the command line.
172 
173  if ( prmstg_f(1:8) .ne. 'NULLPSTG' ) then
174  call parstr ( prmstg_f, ptag, mxprms, nptag, ',', .false. )
175  if ( nptag .gt. 0 ) then
176  do ii = 1, nptag
177  call parstr ( ptag(ii), pvtag, 2, npvtag, '=', .false. )
178  if ( npvtag .eq. 2 ) then
179  call strsuc ( pvtag(1), cprmnm, lcprmnm )
180  call strnum ( pvtag(2), ipval, iersn )
181  if ( ( lcprmnm .gt. 0 ) .and. ( iersn .ne. -1 ) ) then
182  if ( isetprm( cprmnm(1:lcprmnm), ipval ) .ne. 0 ) then
183  print *, 'Error: Bad return from isetprm for parameter: ', cprmnm(1:lcprmnm)
184  return
185  end if
186  end if
187  end if
188  end do
189  end if
190  end if
191 
192 ! Decide how to process the file.
193 
194  if ( ( idxmsg( ibfmg ) .eq. 1 ) .and. ( forcemt_f .eq. 'N' ) ) then
195 
196 ! The first message in the file is a DX dictionary message, so assume there's an embedded table at the
197 ! front of the file, and use this table to decode it.
198 
199  call openbf ( lunit, 'INUL', lunit )
200  else if ( ( tblfil_f(1:8) .ne. 'NULLFILE' ) .and. ( forcemt_f .eq. 'N' ) ) then
201 
202 ! A DX dictionary tables file was specified on the command line, so use it to decode the BUFR file.
203 
204  inquire ( file = tblfil_f, exist = exists )
205  if ( .not. exists ) then
206  print *, 'Error: Could not find file ', tblfil_f
207  return
208  end if
209  open ( unit = 91, file = tblfil_f, iostat = ier )
210  if ( ier .ne. 0 ) then
211  print *, 'Error: Could not open file ', tblfil_f
212  return
213  endif
214  call openbf ( lunit, 'IN', 91 )
215  else
216 
217 ! Decode the file using the master tables in tbldir_f.
218 
219  usemt = 'Y'
220  call openbf ( lunit, 'SEC3', lunit )
221  end if
222 
223  opened = 'Y'
224 
225  call mtinfo ( tbldir_f, 90, 91 )
226  if ( cfms_f .eq. 'Y' ) call codflg ( 'Y' )
227  end if
228 
229  if ( basic_f .eq. 'N' ) then
230 
231 ! Pass the message to the decoder.
232 
233  call readerme ( ibfmg, lunit, cmgtag, imgdt, ierme )
234  end if
235 
236 ! If this is a DX dictionary message, then don't generate any output unless master tables are being used for decoding.
237 
238  if ( ( idxmsg( ibfmg ) .ne. 1 ) .or. ( usemt .eq. 'Y' ) ) then
239 
240  nmsg = nmsg + 1
241 
242  write ( 51, fmt = '( /, A, I7 )' ) 'Found BUFR message #', nmsg
243 
244 ! Decode and output the data from Section 0.
245 
246  write ( 51, fmt= '( /, A, I9 )' ) ' Message length: ', iupbs01( ibfmg, 'LENM' )
247  write ( 51, fmt= '( A, I4 )' ) ' Section 0 length: ', iupbs01( ibfmg, 'LEN0' )
248  write ( 51, fmt= '( A, I4 )' ) ' BUFR edition: ', iupbs01( ibfmg, 'BEN' )
249 
250 ! Decode and output the data from Section 1.
251 
252  write ( 51, fmt= '( /, A, I4 )' ) ' Section 1 length: ', iupbs01( ibfmg, 'LEN1' )
253  write ( 51, fmt= '( A, I4 )' ) ' Master table: ', iupbs01( ibfmg, 'BMT' )
254 
255  iogce = iupbs01( ibfmg, 'OGCE' )
256  igses = iupbs01( ibfmg, 'GSES' )
257  if ( ( basic_f .eq. 'Y' ) .or. ( cfms_f .eq. 'N' ) ) then
258  write ( 51, fmt= '( A, I5 )' ) ' Originating center: ', iogce
259  write ( 51, fmt= '( A, I4 )' ) ' Originating subcenter: ', igses
260  else
261  call getcfmng ( lunit, 'ORIGC', iogce, ' ', -1, cmorgc, lcmorgc, ierorgc )
262  if ( ierorgc .eq. 0 ) then
263  write ( 51, fmt= '( A, I5, 3A )' ) ' Originating center: ', iogce, ' (= ', cmorgc(1:lcmorgc), ')'
264  else
265  write ( 51, fmt= '( A, I5 )' ) ' Originating center: ', iogce
266  end if
267  call getcfmng ( lunit, 'GSES', igses, 'ORIGC', iogce, cmgses, lcmgses, iergses )
268  if ( iergses .eq. 0 ) then
269  write ( 51, fmt= '( A, I4, 3A )' ) ' Originating subcenter: ', igses, ' (= ', cmgses(1:lcmgses), ')'
270  else
271  write ( 51, fmt= '( A, I4 )' ) ' Originating subcenter: ', igses
272  end if
273  end if
274 
275  write ( 51, fmt= '( A, I4 )' ) ' Update sequence numbr: ', iupbs01( ibfmg, 'USN' )
276 
277  if ( iupbs01( ibfmg, 'ISC2' ) .eq. 1 ) then
278  write ( 51, fmt = '( A )') ' Section 2 present?: Yes'
279  else
280  write ( 51, fmt = '( A )') ' Section 2 present?: No'
281  end if
282 
283  mtyp = iupbs01( ibfmg, 'MTYP' )
284  msbt = iupbs01( ibfmg, 'MSBT' )
285  msbti = iupbs01( ibfmg, 'MSBTI' )
286  if ( ( basic_f .eq. 'Y' ) .or. ( cfms_f .eq. 'N' ) ) then
287  write ( 51, fmt= '( A, I4 )' ) ' Data category: ', mtyp
288  write ( 51, fmt= '( A, I4 )' ) ' Local subcategory: ', msbt
289  write ( 51, fmt= '( A, I4 )' ) ' Internatl subcategory: ', msbti
290  else
291  call getcfmng ( lunit, 'TABLAT', mtyp, ' ', -1, cmmtyp, lcmmtyp, iermtyp )
292  if ( iermtyp .eq. 0 ) then
293  write ( 51, fmt= '( A, I4, 3A )' ) ' Data category: ', mtyp, ' (= ', cmmtyp(1:lcmmtyp), ')'
294  else
295  write ( 51, fmt= '( A, I4 )' ) ' Data category: ', mtyp
296  end if
297  call getcfmng ( lunit, 'TABLASL', msbt, 'TABLAT', mtyp, cmmsbt, lcmmsbt, iermsbt )
298  if ( ( iermsbt .eq. 0 ) .and. ( iogce .eq. 7 ) ) then
299  write ( 51, fmt= '( A, I4, 3A )' ) ' Local subcategory: ', msbt, ' (= ', cmmsbt(1:lcmmsbt), ')'
300  else
301  write ( 51, fmt= '( A, I4 )' ) ' Local subcategory: ', msbt
302  end if
303  call getcfmng ( lunit, 'TABLASS', msbti, 'TABLAT', mtyp, cmmsbti, lcmmsbti, iermsbti )
304  if ( iermsbti .eq. 0 ) then
305  write ( 51, fmt= '( A, I4, 3A )' ) ' Internatl subcategory: ', msbti, ' (= ', cmmsbti(1:lcmmsbti), ')'
306  else
307  write ( 51, fmt= '( A, I4 )' ) ' Internatl subcategory: ', msbti
308  end if
309  end if
310 
311  write ( 51, fmt= '( A, I4 )' ) ' Master table version: ', iupbs01( ibfmg, 'MTV' )
312  write ( 51, fmt= '( A, I4 )' ) ' Local table version: ', iupbs01( ibfmg, 'MTVL' )
313  write ( 51, fmt= '( A, I4 )' ) ' Year: ', iupbs01( ibfmg, 'YEAR' )
314  write ( 51, fmt= '( A, I4 )' ) ' Month: ', iupbs01( ibfmg, 'MNTH' )
315  write ( 51, fmt= '( A, I4 )' ) ' Day: ', iupbs01( ibfmg, 'DAYS' )
316  write ( 51, fmt= '( A, I4 )' ) ' Hour: ', iupbs01( ibfmg, 'HOUR' )
317  write ( 51, fmt= '( A, I4 )' ) ' Minute: ', iupbs01( ibfmg, 'MINU' )
318  write ( 51, fmt= '( A, I4 )' ) ' Second: ', iupbs01( ibfmg, 'SECO' )
319  if ( ( iogce .eq. 7 ) .and. ( igses .eq. 3 ) ) then
320  call rtrcptb ( ibfmg, iryr, irmo, irdy, irhr, irmi, irtret )
321  if ( irtret .eq. 0 ) then
322  write ( 51, fmt= '( A, I4 )' ) ' NCEP tank rcpt year: ', iryr
323  write ( 51, fmt= '( A, I4 )' ) ' NCEP tank rcpt month: ', irmo
324  write ( 51, fmt= '( A, I4 )' ) ' NCEP tank rcpt day: ', irdy
325  write ( 51, fmt= '( A, I4 )' ) ' NCEP tank rcpt hour: ', irhr
326  write ( 51, fmt= '( A, I4 )' ) ' NCEP tank rcpt minute: ', irmi
327  end if
328  end if
329 
330 ! Decode and output the data from Section 3.
331 
332  nsub = iupbs3( ibfmg, 'NSUB' )
333  write ( 51, fmt= '( /, A, I4 )' ) ' Number of data subsets: ', nsub
334  nsubt = nsubt + nsub
335 
336  if ( iupbs3( ibfmg, 'IOBS' ) .eq. 1 ) then
337  write ( 51, fmt = '( A )') ' Data are observed?: Yes'
338  else
339  write ( 51, fmt = '( A )') ' Data are observed?: No'
340  end if
341 
342  if ( iupbs3( ibfmg, 'ICMP' ) .eq. 1 ) then
343  write ( 51, fmt = '( A )') ' Data are compressed?: Yes'
344  else
345  write ( 51, fmt = '( A )') ' Data are compressed?: No'
346  end if
347 
348  call upds3 ( ibfmg, mxds3, cds3, nds3 )
349  write ( 51, fmt= '( A, I5 )' ) ' Number of descriptors: ', nds3
350  do jj = 1, nds3
351  write ( 51, fmt = '( 5X, I4, A, A6)' ) jj, ": ", cds3( jj )
352  end do
353 
354  if ( ( basic_f .eq. 'N' ) .and. ( ierme .ge. 0 ) ) then
355 
356 ! Decode and output the data from Section 4.
357 
358  write ( 51, fmt = '( /, A, I7, 3A, I10, A, I6, A )' ) &
359  'BUFR message #', nmsg, ' of type ', cmgtag, ' and date ', imgdt, ' contains ', nsub, ' subsets:'
360  do while ( ireadsb( lunit ) .eq. 0 )
361  call ufdump ( lunit, 51 )
362  end do
363  end if
364 
365  write ( 51, fmt = '( /, A, I7 )' ) 'End of BUFR message #', nmsg
366  write ( 51, fmt = '( /, 120("-"))' )
367  end if
368 
369  end do
370 
371  return
372 end subroutine fdebufr_c
373 
388 subroutine openbt ( lundx, mtyp )
389 
390  use share_table_info
391 
392  implicit none
393 
394  character*11 bftab
395  character*520 bftabfil
396 
397  integer, intent(in) :: mtyp
398  integer, intent(out) :: lundx
399 
400  logical exists
401 
402  write ( bftab, '("bufrtab.",i3.3)' ) mtyp
403  bftabfil = tbldir_f(1:ltbd) // '/' // bftab
404 
405  inquire ( file = bftabfil, exist = exists )
406  if ( exists ) then
407  lundx = ludx
408  close ( lundx )
409  open ( unit = lundx, file = bftabfil )
410  else
411  lundx = 0
412  end if
413 
414  return
415 end subroutine openbt
subroutine codflg(CF)
This subroutine is used to specify whether or not code and flag table information should be included ...
Definition: codflg.f:41
recursive subroutine datelen(LEN)
This subroutine is used to specify the format of Section 1 date-time values that will be output by fu...
Definition: datelen.f:28
subroutine fdebufr_c(ofile, lenof, tbldir, lentd, tblfil, lentf, prmstg, lenps, basic, forcemt, cfms)
This subroutine reads, decodes, and generates a verbose output listing of the contents of every BUFR ...
Definition: debufr.F90:58
recursive subroutine dxdump(LUNIT, LDXOT)
This subroutine prints a copy of the DX BUFR table associated with a specified Fortran logical unit.
Definition: dxdump.f:39
recursive subroutine getcfmng(LUNIT, NEMOI, IVALI, NEMOD, IVALD, CMEANG, LNMNG, IRET)
This subroutine searches for a specified Table B mnemonic and associated value (code figure or bit nu...
Definition: getcfmng.f:105
recursive subroutine mtinfo(CMTDIR, LUNMT1, LUNMT2)
Specify the directory location and Fortran logical unit numbers to be used when reading master BUFR t...
Definition: mtinfo.f:39
Wrap C NCEPLIBS-bufr functions so they can be called from within Fortran application programs.
This module is used within the debufr utility to share information between subroutine fdebufr_c() and...
Definition: debufr.F90:11
integer ludx
Fortran logical unit number to use for referencing a DX table.
Definition: debufr.F90:20
integer ltbd
Length (in characters) of tbldir_f.
Definition: debufr.F90:17
character(len=:), allocatable tbldir_f
Directory containing DX BUFR tables to be used for decoding.
Definition: debufr.F90:14
recursive subroutine openbf(LUNIT, IO, LUNDX)
Connects a new file to the NCEPLIBS-bufr software for input or output operations, or initializes the ...
Definition: openbf.f:124
recursive subroutine openbt(LUNDX, MTYP)
This subroutine is called as a last resort from within subroutine cktaba(), in the event the latter s...
Definition: openbt.f:36
subroutine parstr(STR, TAGS, MTAG, NTAG, SEP, LIMIT80)
Parse a string containing one or more substrings into an array of substrings.
Definition: parstr.f:24
recursive subroutine readerme(MESG, LUNIT, SUBSET, JDATE, IRET)
Read a BUFR message from a memory array.
Definition: readerme.f:52
recursive subroutine rtrcptb(MBAY, IYR, IMO, IDY, IHR, IMI, IRET)
This subroutine reads the tank receipt time (if one exists) from Section 1 of a BUFR message.
Definition: rtrcptb.f:26
recursive subroutine strnum(str, num, iret)
Decode an integer from a character string.
Definition: strnum.F90:24
subroutine strsuc(str1, str2, lens)
This subroutine removes leading and trailing blanks from a character string.
Definition: strsuc.F90:16
recursive subroutine ufdump(LUNIT, LUPRT)
This subroutine prints a verbose listing of the contents of a data subset, including all data values ...
Definition: ufdump.f:44
recursive subroutine upds3(MBAY, LCDS3, CDS3, NDS3)
This subroutine returns the sequence of data descriptors contained within Section 3 of a BUFR message...
Definition: upds3.f:26