NCEPLIBS-bufr  12.0.0
ufdump.f
Go to the documentation of this file.
1 C> @file
2 C> @brief Print the contents of a data subset.
3 C>
4 C> @authors J. Woollen, J. Ator @date 2002-05-14
5 
6 C> This subroutine prints a verbose listing of the contents of a data
7 C> subset, including all data values and replicated sequences, as well
8 C> as the meanings of data values which are code or flag table entries.
9 C>
10 C> This subroutine is similar to subroutine ufbdmp(), but it prints
11 C> different characteristics of each data subset, and in a slightly
12 C> different format. However, both subroutines can be useful for
13 C> different diagnostic purposes, and both can also be run
14 C> interactively to scroll through the contents of a data subset.
15 C>
16 C> Logical unit LUNIT should have already been opened for
17 C> input operations via a previous call to subroutine openbf(), and a
18 C> BUFR data subset should have already been read into internal arrays
19 C> via a previous call to one of the
20 C> [subset-reading subroutines](@ref hierarchy).
21 C>
22 C> Except when LUPRT = 0, logical unit LUPRT must already be
23 C> associated with a filename on the local system, typically via a
24 C> Fortran "OPEN" statement. When LUPRT = 0, the subroutine will run
25 C> interactively and print to standard output, scrolling 20 lines at
26 C> a time and prompting each time whether to quit and return to the
27 C> application program (by typing 'q' then '<Enter>') or continue
28 C> scrolling (by typing anything else).
29 C>
30 C> In order for the meanings of code and flag table values to be
31 C> included in the output, a previous call to subroutine codflg()
32 C> must have been made with argument CF = 'Y'. Otherwise, only the
33 C> code and flag table values themselves will be printed.
34 C>
35 C> @param[in] LUNIT -- integer: Fortran logical unit number for
36 C> BUFR file
37 C> @param[in] LUPRT -- integer: Fortran logical unit number for
38 C> print output
39 C> - 0 = Run interactively, printing to
40 C> standard output
41 C>
42 C> @authors J. Woollen, J. Ator @date 2002-05-14
43  RECURSIVE SUBROUTINE ufdump(LUNIT,LUPRT)
44 
45  use bufrlib
46 
47  USE modv_im8b
48 
49  USE moda_usrint
50  USE moda_msgcwd
51  USE moda_tababd
52  USE moda_tables
53  USE moda_nrv203
54 
55  COMMON /tablef/ cdmf
56 
57  CHARACTER*120 cfmeang
58  CHARACTER*80 fmt
59  CHARACTER*64 desc
60  CHARACTER*24 unit
61  CHARACTER*120 lchr2
62  CHARACTER*20 lchr,pmiss
63  CHARACTER*15 nemo3
64  CHARACTER*10 nemo,nemo2,tagrfe
65  CHARACTER*8 nemod
66  CHARACTER*6 numb
67  CHARACTER*7 fmtf
68  CHARACTER*8 cval
69  CHARACTER*3 type
70  CHARACTER*1 cdmf,tab,you
71  equivalence(rval,cval)
72  real*8 rval
73  LOGICAL track,found,rdrv
74 
75  parameter(mxcfdp=5)
76  INTEGER icfdp(mxcfdp)
77 
78  parameter(mxfv=31)
79  INTEGER ifv(mxfv)
80 
81  parameter(mxseq=10)
82  INTEGER idxrep(mxseq)
83  INTEGER numrep(mxseq)
84  CHARACTER*10 seqnam(mxseq)
85  INTEGER lsqnam(mxseq)
86 
87  parameter(mxls=10)
88  CHARACTER*10 lsnemo(mxls)
89  INTEGER lsct(mxls)
90 
91  DATA pmiss /' MISSING'/
92  DATA you /'Y'/
93 
94 C----------------------------------------------------------------------
95 C----------------------------------------------------------------------
96 
97 C CHECK FOR I8 INTEGERS
98 C ---------------------
99 
100  IF(im8b) THEN
101  im8b=.false.
102 
103  CALL x84(lunit,my_lunit,1)
104  CALL x84(luprt,my_luprt,1)
105  CALL ufdump(my_lunit,my_luprt)
106 
107  im8b=.true.
108  RETURN
109  ENDIF
110 
111  nseq = 0
112  nls = 0
113  lcfmeang = len(cfmeang)
114 
115  IF(luprt.EQ.0) THEN
116  luout = 6
117  ELSE
118  luout = luprt
119  ENDIF
120 
121 C CHECK THE FILE STATUS AND I-NODE
122 C --------------------------------
123 
124  CALL status(lunit,lun,il,im)
125  IF(il.EQ.0) GOTO 900
126  IF(il.GT.0) GOTO 901
127  IF(im.EQ.0) GOTO 902
128  IF(inode(lun).NE.inv(1,lun)) GOTO 903
129 
130  WRITE(luout,fmt='(/,2A,/)') 'MESSAGE TYPE ',tag(inode(lun))
131 
132 C DUMP THE CONTENTS OF MODULE USRINT FOR UNIT LUNIT
133 C -------------------------------------------------
134 
135 C If code/flag table details are being printed, and if this is the
136 C first subset of a new message, then make sure the appropriate
137 C master tables have been read in to memory for this message.
138 
139  IF(cdmf.EQ.'Y' .AND. nsub(lun).EQ.1) itmp = ireadmt(lun)
140 
141  DO nv=1,nval(lun)
142  IF(luprt.EQ.0 .AND. mod(nv,20).EQ.0) THEN
143 
144 C When LUPRT=0, the output will be scrolled, 20 elements at a time
145 C ----------------------------------------------------------------
146 
147  print*,'(<enter> for MORE, q <enter> to QUIT)'
148  READ(5,'(A1)') you
149 
150 C If the terminal enters "q" followed by "<enter>" after the prompt
151 C "(<enter> for MORE, q <enter> to QUIT)", scrolling will end and the
152 C subroutine will return to the calling program
153 C -------------------------------------------------------------------
154 
155  IF(you.EQ.'q') THEN
156  print*
157  print*,'==> You have chosen to stop the dumping of this subset'
158  print*
159  GOTO 100
160  ENDIF
161  ENDIF
162 
163  node = inv(nv,lun)
164  nemo = tag(node)
165  ityp = itp(node)
166  TYPE = typ(node)
167 
168  IF(ityp.GE.1.AND.ityp.LE.3) THEN
169  CALL nemtab(lun,nemo,idn,tab,n)
170  if(n>0) then
171  numb = tabb(n,lun)(1:6)
172  desc = tabb(n,lun)(16:70)
173  unit = tabb(n,lun)(71:94)
174  endif
175  rval = val(nv,lun)
176  ENDIF
177 
178  IF((ityp.EQ.0).OR.(ityp.EQ.1)) THEN
179 
180 C Sequence descriptor or delayed descriptor replication factor
181 
182  IF((type.EQ.'REP').OR.(type.EQ.'DRP').OR.
183  . (type.EQ.'DRB').OR.(type.EQ.'DRS')) THEN
184 
185 C Print the number of replications
186 
187  nseq = nseq+1
188  IF(nseq.GT.mxseq) GOTO 904
189  IF(type.EQ.'REP') THEN
190  numrep(nseq) = irf(node)
191  ELSE
192  numrep(nseq) = nint(rval)
193  ENDIF
194  CALL strsuc(nemo,nemo2,lnm2)
195  fmt = '(11X,A,I6,1X,A)'
196  WRITE(luout,fmt) nemo2(1:lnm2), numrep(nseq), 'REPLICATIONS'
197 
198 C How many times is this sequence replicated?
199 
200  IF(numrep(nseq).GT.1) THEN
201 
202 C Track the sequence
203 
204  seqnam(nseq) = nemo2
205  lsqnam(nseq) = lnm2
206  idxrep(nseq) = 1
207  ELSE
208 
209 C Don't bother
210 
211  nseq = nseq-1
212  ENDIF
213  ELSEIF( ((type.EQ.'SEQ').OR.(type.EQ.'RPC').OR.(type.EQ.'RPS'))
214  . .AND. (nseq.GT.0) ) THEN
215 
216 C Is this one of the sequences being tracked?
217 
218  ii = nseq
219  track = .false.
220  CALL strsuc(nemo,nemo2,lnm2)
221  DO WHILE ((ii.GE.1).AND.(.NOT.track))
222  IF(nemo2(1:lnm2).EQ.seqnam(ii)(2:lsqnam(ii)-1)) THEN
223  track = .true.
224 
225 C Mark this level in the output
226 
227  fmt = '(4X,A,2X,A,2X,A,I6,2X,A)'
228  WRITE(luout,fmt) '++++++', nemo2(1:lnm2),
229  . 'REPLICATION #', idxrep(ii), '++++++'
230  IF(idxrep(ii).LT.numrep(ii)) THEN
231 
232 C There are more levels to come
233 
234  idxrep(ii) = idxrep(ii)+1
235  ELSE
236 
237 C This was the last level for this sequence, so stop
238 C tracking it
239 
240  nseq = nseq-1
241  ENDIF
242  ELSE
243  ii = ii-1
244  ENDIF
245  ENDDO
246  ENDIF
247  ELSEIF(ityp.EQ.2) THEN
248 
249 C Other numeric value
250 
251 C First check if this node contains a redefined reference
252 C value. If so, modify the DESC field to label it as such.
253 
254  jj = 1
255  rdrv = .false.
256  DO WHILE ((jj.LE.nnrv).AND.(.NOT.rdrv))
257  IF (node.EQ.inodnrv(jj)) THEN
258  rdrv = .true.
259  desc = 'New reference value for ' // nemo
260  unit = ' '
261  ELSE
262  jj = jj + 1
263  ENDIF
264  ENDDO
265 
266 C Check if this element refers to another element via a bitmap.
267 C If so, modify the DESC field to identify the referred element.
268 
269  nrfe = nrfelm(nv,lun)
270  IF(nrfe.GT.0) THEN
271  tagrfe = tag(inv(nrfe,lun))
272  jj = 48
273  DO WHILE((jj.GE.1).AND.(desc(jj:jj).EQ.' '))
274  jj = jj - 1
275  ENDDO
276  IF(jj.LE.33) desc(jj+1:jj+15) = ' for ' // tagrfe
277  ENDIF
278 
279 C Now print the value
280 
281  IF(ibfms(rval).NE.0) THEN
282 
283 C The value is "missing".
284 
285  fmt = '(A6,2X,A10,2X,A20,2X,A24,6X,A48)'
286  WRITE(luout,fmt) numb,nemo,pmiss,unit,desc
287  ELSE
288  fmt = '(A6,2X,A10,2X,F20.00,2X,A24,6X,A48)'
289 
290 C Based upon the corresponding scale factor, select an
291 C appropriate format for the printing of this value.
292 
293  WRITE(fmt(19:20),'(I2)') max(1,isc(node))
294  IF(unit(1:4).EQ.'FLAG') THEN
295 
296 C Print a listing of the bits corresponding to
297 C this value.
298 
299  CALL upftbv(lunit,nemo,rval,mxfv,ifv,nifv)
300  IF(nifv.GT.0) THEN
301  unit(11:11) = '('
302  ipt = 12
303  DO ii=1,nifv
304  isz = isize(ifv(ii))
305  WRITE(fmtf,'(A2,I1,A4)') '(I', isz, ',A1)'
306  IF((ipt+isz).LE.24) THEN
307  WRITE(unit(ipt:ipt+isz),fmtf) ifv(ii), ','
308  ipt = ipt + isz + 1
309  ELSE
310  unit(12:23) = 'MANY BITS ON'
311  ipt = 25
312  ENDIF
313  ENDDO
314  unit(ipt-1:ipt-1) = ')'
315  ENDIF
316  ENDIF
317 
318  WRITE(luout,fmt) numb,nemo,rval,unit,desc
319 
320  IF( (unit(1:4).EQ.'FLAG' .OR. unit(1:4).EQ.'CODE') .AND.
321  . (cdmf.EQ.'Y') ) THEN
322 
323 C Print the meanings of the code and flag values.
324 
325  fmt = '(31X,I8,A,A)'
326  IF(unit(1:4).EQ.'CODE') THEN
327  nifv = 1
328  ifv(nifv) = nint(rval)
329  ENDIF
330  DO ii=1,nifv
331  icfdp(1) = (-1)
332  CALL srchtbf_c(idn,ifv(ii),icfdp(1),mxcfdp,-1,
333  . cfmeang,lcfmeang,lcfmg,iersf)
334  IF(iersf.EQ.0) THEN
335  WRITE(luout,fmt) ifv(ii),' = ',cfmeang(1:lcfmg)
336  ELSEIF(iersf.LT.0) THEN
337  WRITE(luout,fmt) ifv(ii),' = ',
338  . '***THIS IS AN ILLEGAL/UNDEFINED VALUE***'
339  ELSE
340 
341 C The meaning of this value is dependent on the
342 C value of another mnemonic in the report. Look for
343 C that other mnemonic within the report and then use
344 C it and its associated value to retrieve and print
345 C the proper meaning from the code/flag tables.
346 
347  ierft = (-1)
348  jj = 0
349  DO WHILE((jj.LT.iersf).AND.(ierft.LT.0))
350  jj = jj + 1
351  CALL numtbd(lun,icfdp(jj),nemod,tab,ierbd)
352  IF((ierbd.GT.0).AND.(tab.EQ.'B')) THEN
353  CALL fstag(lun,nemod,-1,nv,nout,ierft)
354  ENDIF
355  ENDDO
356  IF(ierft.EQ.0) THEN
357  ifvd = nint(val(nout,lun))
358  IF(jj.GT.1) icfdp(1) = icfdp(jj)
359  CALL srchtbf_c(idn,ifv(ii),icfdp(1),mxcfdp,ifvd,
360  . cfmeang,lcfmeang,lcfmg,iersf)
361  IF(iersf.EQ.0) THEN
362  WRITE(luout,fmt) ifv(ii),' = ',
363  . cfmeang(1:lcfmg)
364  ENDIF
365  ENDIF
366  ENDIF
367  ENDDO
368  ENDIF
369  ENDIF
370  ELSEIF(ityp.EQ.3) THEN
371 
372 C Character (CCITT IA5) value
373 
374  nchr = ibt(node)/8
375 
376  IF(ibfms(rval).NE.0) THEN
377  lchr = pmiss
378  ELSE IF(nchr.LE.8) THEN
379  lchr = cval
380  ELSE
381 
382 C Track the number of occurrences of this long character string, so
383 C that we can properly output each one.
384 
385  ii = 1
386  found = .false.
387  DO WHILE((ii.LE.nls).AND.(.NOT.found))
388  IF(nemo.EQ.lsnemo(ii)) THEN
389  found = .true.
390  ELSE
391  ii = ii + 1
392  ENDIF
393  ENDDO
394 
395  IF(.NOT.found) THEN
396  nls = nls+1
397  IF(nls.GT.mxls) GOTO 905
398  lsnemo(nls) = nemo
399  lsct(nls) = 1
400  nemo3 = nemo
401  ELSE
402  CALL strsuc(nemo,nemo3,lnm3)
403  lsct(ii) = lsct(ii) + 1
404  WRITE(fmtf,'(A,I1,A)') '(2A,I', isize(lsct(ii)), ')'
405  WRITE(nemo3,fmtf) nemo(1:lnm3), '#', lsct(ii)
406  ENDIF
407 
408  CALL readlc(lunit,lchr2,nemo3)
409  IF (icbfms(lchr2,nchr).NE.0) THEN
410  lchr = pmiss
411  ELSE
412  lchr = lchr2(1:20)
413  ENDIF
414  ENDIF
415 
416  IF ( nchr.LE.20 .OR. lchr.EQ.pmiss ) THEN
417  lchr = adjustr(lchr)
418  fmt = '(A6,2X,A10,2X,A20,2X,"(",I2,")",A24,2X,A48)'
419  WRITE(luout,fmt) numb,nemo,lchr,nchr,unit,desc
420  ELSE
421  fmt = '(A6,2X,A10,2X,A,2X,"(",I3,")",A23,2X,A48)'
422  WRITE(luout,fmt) numb,nemo,lchr2(1:nchr),nchr,unit,desc
423  ENDIF
424  ENDIF
425 
426  ENDDO
427 
428  WRITE(luout,3)
429 3 FORMAT(/' >>> END OF SUBSET <<< '/)
430 
431 C EXITS
432 C -----
433 
434 100 RETURN
435 900 CALL bort('BUFRLIB: UFDUMP - INPUT BUFR FILE IS CLOSED, IT '//
436  . 'MUST BE OPEN FOR INPUT')
437 901 CALL bort('BUFRLIB: UFDUMP - INPUT BUFR FILE IS OPEN FOR '//
438  . 'OUTPUT, IT MUST BE OPEN FOR INPUT')
439 902 CALL bort('BUFRLIB: UFDUMP - A MESSAGE MUST BE OPEN IN INPUT '//
440  . 'BUFR FILE, NONE ARE')
441 903 CALL bort('BUFRLIB: UFDUMP - LOCATION OF INTERNAL TABLE FOR '//
442  . 'INPUT BUFR FILE DOES NOT AGREE WITH EXPECTED LOCATION IN '//
443  . 'INTERNAL SUBSET ARRAY')
444 904 CALL bort('BUFRLIB: UFDUMP - MXSEQ OVERFLOW')
445 905 CALL bort('BUFRLIB: UFDUMP - MXLS OVERFLOW')
446  END
subroutine bort(STR)
Log one error message and abort application program.
Definition: bort.f:18
subroutine fstag(LUN, UTAG, NUTAG, NIN, NOUT, IRET)
This subroutine finds the (NUTAG)th occurrence of mnemonic UTAG within the current overall subset def...
Definition: fstag.f:26
integer function ibfms(R8VAL)
Test whether a real*8 data value is "missing".
Definition: ibfms.f:28
recursive function icbfms(STR, LSTR)
This function provides a handy way to check whether a character string returned from a previous call ...
Definition: icbfms.f:25
integer function ireadmt(LUN)
Check whether master BUFR tables need to be read from the local file system.
Definition: ireadmt.f:36
integer function isize(NUM)
This function computes and returns the number of characters needed to encode the input integer NUM as...
Definition: isize.f:19
Wrap C NCEPLIBS-bufr functions so they can be called from within the Fortran part of the library.
Definition: bufrlib.F90:11
This module contains declarations for arrays used to store information about the current BUFR message...
integer, dimension(:), allocatable inode
Table A mnemonic for type of BUFR message.
integer, dimension(:), allocatable nsub
Current subset pointer within message.
This module contains array and variable declarations for use with any 2-03-YYY (change reference valu...
integer nnrv
Number of entries in the jump/link table which contain new reference values (up to a maximum of MXNRV...
integer, dimension(:), allocatable inodnrv
Entries within jump/link table which contain new reference values.
This module contains array and variable declarations used to store DX BUFR tables internally for mult...
character *128, dimension(:,:), allocatable tabb
Table B entries for each internal I/O stream.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable irf
Reference values corresponding to tag and typ:
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
integer, dimension(:), allocatable ibt
Bit widths corresponding to tag and typ:
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
This module contains declarations for arrays used to store data values and associated metadata for th...
integer, dimension(:), allocatable nval
Number of data values in BUFR data subset.
real *8, dimension(:,:), allocatable, target val
Data values.
integer, dimension(:,:), allocatable, target inv
Inventory pointer which links each data value to its corresponding node in the internal jump/link tab...
integer, dimension(:,:), allocatable nrfelm
Referenced data value, for data values which refer to a previous data value in the BUFR data subset v...
This module declares and initializes the IM8B variable.
logical, public im8b
Status indicator to keep track of whether all future calls to BUFRLIB subroutines and functions from ...
subroutine nemtab(LUN, NEMO, IDN, TAB, IRET)
Get information about a descriptor, based on the mnemonic.
Definition: nemtab.f:29
subroutine numtbd(LUN, IDN, NEMO, TAB, IRET)
Search for a Table B or Table D descriptor within the internal DX BUFR tables.
Definition: numtbd.f:24
recursive subroutine readlc(LUNIT, CHR, STR)
Read a long character string (greater than 8 bytes) from a data subset.
Definition: readlc.f:50
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
Definition: status.f:36
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 upftbv(LUNIT, NEMO, VAL, MXIB, IBIT, NIB)
Given a Table B mnemonic with flag table units and a corresponding numerical data value,...
Definition: upftbv.f:28
subroutine x84(IIN8, IOUT4, NVAL)
Encode one or more 8-byte integer values as 4-byte integer values.
Definition: x84.F:19